[commit] r2248 - Improved build instructions. Merged fix for NetBSD to unix UUID plugin.

Previous Topic Next Topic
 
classic Classic list List threaded Threaded
1 message Options
Reply | Threaded
Open this post in threaded view
|

[commit] r2248 - Improved build instructions. Merged fix for NetBSD to unix UUID plugin.

commits-3
 
Author: eliot
Date: 2010-07-22 18:09:10 -0700 (Thu, 22 Jul 2010)
New Revision: 2248

Modified:
   branches/Cog/image/VMMaker-Squeak4.1.changes
   branches/Cog/image/VMMaker-Squeak4.1.image
   branches/Cog/platforms/unix/plugins/UUIDPlugin/sqUnixUUID.c
   branches/Cog/unixbuild/HowToBuild
Log:
Improved build instructions.  Merged fix for NetBSD to unix UUID plugin.


Modified: branches/Cog/image/VMMaker-Squeak4.1.changes
===================================================================
--- branches/Cog/image/VMMaker-Squeak4.1.changes 2010-07-22 03:52:11 UTC (rev 2247)
+++ branches/Cog/image/VMMaker-Squeak4.1.changes 2010-07-23 01:09:10 UTC (rev 2248)
@@ -124068,4 +124068,291 @@
 ----STARTUP----{20 July 2010 . 1:14:28 pm} as /Users/eliot/Cog/oscog/Cog.squeakvm.org/image/VMMaker-Squeak4.1.image!
 
 
-----QUIT/NOSAVE----{20 July 2010 . 1:14:37 pm} VMMaker-Squeak4.1.image priorSource: 5004308!
\ No newline at end of file
+----QUIT/NOSAVE----{20 July 2010 . 1:14:37 pm} VMMaker-Squeak4.1.image priorSource: 5004308!
+
+----STARTUP----{22 July 2010 . 5:55:14 pm} as /Users/eliot/Cog/oscog/Cog.squeakvm.org/image/VMMaker-Squeak4.1.image!
+
+
+----QUIT/NOSAVE----{22 July 2010 . 5:55:25 pm} VMMaker-Squeak4.1.image priorSource: 5004308!
+
+----STARTUP----{22 July 2010 . 5:56:26 pm} as /Users/eliot/Cog/oscog/Cog.squeakvm.org/image/VMMaker-Squeak4.1.image!
+
+
+Point removeSelector: #basicType!
+!CachedBlockClosure commentStamp: 'eem 7/22/2010 12:34' prior: 0!
+I'm a BlockClosure with an added instance variable for storing the once upon a time result of evaluating myself when I was simple BlockClosure. This is triggered by sending #once to a normal BlockClosure. Future sends of once will simply return this value rather than evaluate myself. When sent value, I revert back to a BlockClosure.  Originally by Travis Griggs, from whom we copy this idea with thanks.
+
+Instance Variables
+ cachedValue <Object>
+
+cachedValue
+ - result of having sent value to myself when i was just a BlockClosure!
+!BlockClosure methodsFor: 'private' stamp: 'eem 7/22/2010 12:23'!
+becomeCached
+ self become: ((CachedBlockClosure new: self size)
+ outerContext: outerContext
+ startpc: startpc
+ numArgs: numArgs
+ cachedValue: self value
+ copiedValues: self)! !
+!BlockClosure methodsFor: 'private' stamp: 'eem 7/22/2010 12:19'!
+becomeUncached
+ "The receiver is already uncached."
+ ^self! !
+!BlockClosure methodsFor: 'evaluating' stamp: 'eem 7/22/2010 12:52'!
+once
+ "Answer and remember my value, answering exactly the same object in any further sends
+ of once or value until I become uncached.  This allows one to intern values with the idiom
+ myResourceMethod
+ ^[expression] once.
+ The expression will be evaluated once and its result returned for any subsequent evaluations.
+ Originally by Travis Griggs, from whom we copy this idea with thanks."
+ numArgs ~= 0 ifTrue:
+ [self error: 'once should only be used with niladic blocks'].
+ self becomeCached.
+ ^self once! !
+!CachedBlockClosure methodsFor: 'private' stamp: 'eem 7/22/2010 12:24'!
+becomeCached
+ "The receiver is already cached."
+ ^self! !
+!CachedBlockClosure methodsFor: 'private' stamp: 'eem 7/22/2010 12:21'!
+becomeUncached
+ self become: (BlockClosure
+ outerContext: outerContext
+ startpc: startpc
+ numArgs: numArgs
+ copiedValues: self)! !
+!CachedBlockClosure methodsFor: 'evaluating' stamp: 'eem 7/22/2010 12:24'!
+once
+ ^cachedValue! !
+!CachedBlockClosure methodsFor: 'initialize-release' stamp: 'eem 7/22/2010 12:16'!
+outerContext: aContext startpc: aStartpc numArgs: argCount cachedValue: aValue copiedValues: anArrayOrNil
+ cachedValue := aValue.
+ super outerContext: aContext startpc: aStartpc numArgs: argCount copiedValues: anArrayOrNil! !
+!CachedBlockClosure methodsFor: 'evaluating' stamp: 'eem 7/22/2010 12:17'!
+value
+ ^cachedValue! !
+!MCHttpRepository methodsFor: 'required' stamp: 'ar 7/21/2010 19:53' prior: 54759713!
+writeStreamForFileNamed: aString replace: ignoreBoolean do: aBlock
+ | stream response statusLine code |
+ stream := RWBinaryOrTextStream on: String new.
+ aBlock value: stream.
+ self displayProgress: 'Uploading ', aString during:[
+ response := HTTPSocket
+ httpPut: stream contents
+ to: (self urlForFileNamed: aString)
+ user: self user
+ passwd: self password.
+ ].
+ "More robust handling of HTTP responses. Instead of enumerating
+ all possible return codes and http versions, do a quick parse"
+ (response beginsWith: 'HTTP/') ifTrue:[
+ "Looks like an HTTP header, not some error message"
+ statusLine := response copyUpTo: Character cr.
+ code := [(statusLine findTokens: ' ') second asInteger] on: Error do:[].
+ ].
+ (code isInteger and:[code between: 200 and: 299])
+ ifFalse:[self error: response].! !
+
+"Monticello"!
+!SimpleButtonMorph commentStamp: 'ul 7/22/2010 04:30' prior: 29085281!
+I am labeled, rectangular morph which allows the user to click me. I can be configured to send my "target" the message "actionSelector" with "arguments" when I am clicked. I may have a label, implemented as a StringMorph.
+
+Example:
+
+ SimpleButtonMorph new
+ target: Beeper;
+ label: 'Beep!!';
+ actionSelector: #beep;
+ openInWorld
+
+Structure:
+instance var Type Description
+target Object The Object to notify upon a click
+actionSelector Symbol The message to send to Target (#messageName)
+arguments Array Arguments to send with #actionSelection (optional)
+actWhen Symbol When to take action: may be #buttonUp (default), #buttonDown,
+ #whilePressed, or #startDrag
+oldColor Color Used to restore color after click
+
+Another example: a button which quits the image without saving it.
+
+ SimpleButtonMorph new
+ target: Smalltalk;
+ label: 'quit';
+ actionSelector: #snapshot:andQuit:;
+ arguments: (Array with: false with: true);
+ openInWorld
+
+!
+!Morph class methodsFor: 'new-morph participation' stamp: 'ar 7/21/2010 20:03'!
+partName: aName categories: aList documentation: aDoc sampleImageForm: aForm
+ "Answer a DescriptionForPartsBin which will represent a launch of a new instance of my class via the #newStandAlone protocol sent to my class. Use the category-list and documentation provided.  This variant allows an overriding image form to be provided, useful in cases where we don't want to launch a sample instance just to get the form"
+
+ | descr |
+ descr := DescriptionForPartsBin new
+ formalName: aName
+ categoryList: aList
+ documentation: aDoc
+ globalReceiverSymbol: self name
+ nativitySelector: #newStandAlone.
+ descr sampleImageForm: aForm.
+ ^ descr
+! !
+
+"Morphic"!
+!SmalltalkImage methodsFor: 'system attributes' stamp: 'eem 7/22/2010 17:44'!
+flagInterpretedMethods: aBoolean
+ "The Cog VM can be instructed to set the flag bit of CompiledMethods that
+ it executes but will only interpret.  This can be used e.g. to profile startup.
+ See CompiledMethod>>#flag & CompiledMethod>>#clearFlag.  
+ This flag persists across snapshots, stored in the image header."
+
+ self vmParameterAt: 48 put: ((self vmParameterAt: 48) bitClear: 2) + (aBoolean ifTrue: [2] ifFalse: [0])! !
+!SmalltalkImage methodsFor: 'system attributes' stamp: 'eem 7/6/2010 20:43' prior: 37392261!
+isRunningCog
+ "Returns true if we're running on a Cog VM (JIT or StackInterpreter)
+ (vmParameterAt: 42 is the number of stack pages)"
+
+ ^[(self vmParameterAt: 42) > 0] on: Error do:[:ex| ex return: false]! !
+!SmalltalkImage methodsFor: 'system attributes' stamp: 'eem 7/6/2010 20:41'!
+isRunningCogit
+ "Returns true if we're running on the Cog JIT
+ (vmParameterAt: 46 is the size of the machine code zone)"
+
+ ^[(self vmParameterAt: 46) > 0] on: Error do:[:ex| ex return: false]! !
+!SmalltalkImage methodsFor: 'system attributes' stamp: 'eem 7/22/2010 17:23'!
+processHasThreadIdInstVar: aBoolean
+ "The threaded VM needs to know if the 4th inst var of Process
+ is threadId which it uses to control process-to-thread binding.
+ This flag persists across snapshots, stored in the image header."
+ aBoolean ifTrue: [self assert: (Process instVarNames at: 4) ='threadId'].
+ self vmParameterAt: 48 put: ((self vmParameterAt: 48) bitClear: 1) + (aBoolean ifTrue: [1] ifFalse: [0])! !
+!SmalltalkImage methodsFor: 'system attributes' stamp: 'eem 7/22/2010 17:51'!
+processPreemptionYields
+ "Answer whether the VM causes a process to yield on process preemption,
+ i.e. to put a preempted process at the back of its run queue.  If the parameter
+ is unavailable (non-Cog VMs) or bit 2 (4) is 0 then preemption yields."
+
+ ^(([self vmParameterAt: 48]
+ on: Error
+ do: [:ex| ^true]) allMask: 4) not! !
+!SmalltalkImage methodsFor: 'system attributes' stamp: 'eem 7/22/2010 17:26'!
+processPreemptionYields: aBoolean
+ "The Cog VM can be instructed not to yield on process preemption,
+ i.e. not to put a preempted process at the back of its run queue.  By
+ default preempting a process causes it to yield (Blue Book semantics)
+ which can have unfortunate effects.
+ This flag persists across snapshots, stored in the image header."
+
+ self vmParameterAt: 48 put: ((self vmParameterAt: 48) bitClear: 4) + (aBoolean ifTrue: [0] ifFalse: [4])! !
+!Preferences class methodsFor: 'reacting to change' stamp: 'ar 7/21/2010 20:20' prior: 26931806!
+displaySizeChanged
+ self flag: #todo.
+ "only change font on small-land image"
+ self smallLandFonts.
+ self tinyDisplay
+ ifTrue: [self enable: #scrollBarsNarrow]
+ ifFalse: [self disable: #scrollBarsNarrow].
+ self tinyDisplay
+ ifTrue:[self disable: #biggerHandles]
+ ifFalse:[self enable: #biggerHandles]! !
+!Preferences class methodsFor: 'fonts' stamp: 'ar 7/21/2010 20:13'!
+restoreFontsAfter: aBlock
+
+ "Restore the currently chosen set of standard fonts after
+ evaluating aBlock. Used for tests that modify the default fonts."
+
+ | standardDefaultTextFont standardListFont standardEToysFont standardMenuFont
+ windowTitleFont standardBalloonHelpFont standardCodeFont standardButtonFont |
+
+ standardDefaultTextFont := Preferences standardDefaultTextFont.
+ standardListFont := Preferences standardListFont.
+ standardEToysFont := Preferences standardEToysFont.
+ standardMenuFont := Preferences standardMenuFont.
+ windowTitleFont := Preferences windowTitleFont.
+ standardBalloonHelpFont := Preferences standardBalloonHelpFont.
+ standardCodeFont := Preferences standardCodeFont.
+ standardButtonFont := Preferences standardButtonFont.
+ ^aBlock ensure: [
+ Preferences setSystemFontTo: standardDefaultTextFont.
+ Preferences setListFontTo: standardListFont.
+ Preferences setEToysFontTo: standardEToysFont.
+ Preferences setMenuFontTo: standardMenuFont.
+ Preferences setWindowTitleFontTo: windowTitleFont.
+ Preferences setBalloonHelpFontTo: standardBalloonHelpFont.
+ Preferences setCodeFontTo: standardCodeFont.
+ Preferences setButtonFontTo: standardButtonFont.
+ ].
+! !
+
+Smalltalk processPreemptionYields!
+!CodeHolder methodsFor: 'misc' stamp: 'topa 7/14/2010 16:35'!
+informPossiblyCorruptSource
+
+ | sourcesName |
+ sourcesName := FileDirectory localNameFor: SmalltalkImage current sourcesName.
+ self inform: 'There may be a problem with your sources file!!
+
+The source code for every method should (usually) start with the
+method selector but this is not the case with this method!! You may
+proceed with caution but it is recommended that you get a new source file.
+
+This can happen if you download the "' , sourcesName  , '" file,
+or the ".changes" file you use, as TEXT. It must be transfered
+in BINARY mode, even if it looks like a text file,
+to preserve the CR line ends.
+
+Mac users: This may have been caused by Stuffit Expander.
+To prevent the files above to be converted to Mac line ends
+when they are expanded, do this: Start the program, then
+from Preferences... in the File menu, choose the Cross
+Platform panel, then select "Never" and press OK.
+Then expand the compressed archive again.
+
+(Occasionally, the source code for a method may legitimately
+start with a non-alphabetic character -- for example, Behavior
+method #formalHeaderPartsFor:.  In such rare cases, you can
+happily disregard this warning.)'! !
+!CodeHolder methodsFor: 'message list' stamp: 'topa 7/14/2010 16:47' prior: 50670096!
+sourceStringPrettifiedAndDiffed
+ "Answer a copy of the source code for the selected message, transformed by diffing and pretty-printing exigencies"
+
+ | class selector sourceString |
+ class := self selectedClassOrMetaClass.
+ selector := self selectedMessageName.
+ (class isNil or: [selector isNil]) ifTrue: [^'missing'].
+ sourceString := class ultimateSourceCodeAt: selector ifAbsent: [^'error'].
+ self validateMessageSource: sourceString forSelector: selector inClass: class.
+ (#(#prettyPrint #prettyDiffs)
+ includes: contentsSymbol)
+ ifTrue:
+ [sourceString := class prettyPrinterClass
+ format: sourceString
+ in: class
+ notifying: nil].
+ self showingAnyKindOfDiffs
+ ifTrue: [sourceString := self diffFromPriorSourceFor: sourceString].
+ ^sourceString! !
+!CodeHolder methodsFor: 'message list' stamp: 'topa 7/14/2010 16:46'!
+validateMessageSource: sourceString forSelector: aSelector inClass: theClass
+ "Check whether there is evidence that method source is invalid"
+
+ (theClass parserClass new parseSelector: sourceString asString) = aSelector
+ ifFalse: [self informPossiblyCorruptSource].! !
+
+CodeHolder removeSelector: #validateMessageSource:forSelector:!
+
+"Tools"!
+
+MCFileBasedRepository flushAllCaches!
+
+| user pw |
+Utilities setAuthorInitials.
+user := UIManager default request: 'Unix user name'.
+pw := UIManager default requestPassword: 'Monticello password'.
+MCHttpRepository allSubInstancesDo: [ : rep |
+ rep user: user;
+ password: pw ]!
+
+----QUIT----{22 July 2010 . 6:05:05 pm} VMMaker-Squeak4.1.image priorSource: 5004308!
\ No newline at end of file

Modified: branches/Cog/image/VMMaker-Squeak4.1.image
===================================================================
(Binary files differ)

Modified: branches/Cog/platforms/unix/plugins/UUIDPlugin/sqUnixUUID.c
===================================================================
--- branches/Cog/platforms/unix/plugins/UUIDPlugin/sqUnixUUID.c 2010-07-22 03:52:11 UTC (rev 2247)
+++ branches/Cog/platforms/unix/plugins/UUIDPlugin/sqUnixUUID.c 2010-07-23 01:09:10 UTC (rev 2248)
@@ -1,20 +1,18 @@
 #include <uuid/uuid.h>
 #include "sq.h"
 
-int sqUUIDInit(void)
-{
-  return 1;
-}
+int sqUUIDInit(void) { return 1; }
 
-int sqUUIDShutdown(void)
-{
-  return 1;
-}
+int sqUUIDShutdown(void) { return 1; }
 
 int MakeUUID(char *location)
 {
   uuid_t uuid;
+#if defined(__NetBSD__)
+  uuidgen(&uuid, 1);
+#else
   uuid_generate(uuid);
+#endif
   memcpy((void *)location, (void *)&uuid, sizeof(uuid));
   return 1;
 }

Modified: branches/Cog/unixbuild/HowToBuild
===================================================================
--- branches/Cog/unixbuild/HowToBuild 2010-07-22 03:52:11 UTC (rev 2247)
+++ branches/Cog/unixbuild/HowToBuild 2010-07-23 01:09:10 UTC (rev 2248)
@@ -46,3 +46,15 @@
      ../../platforms/unix/config/configure CC="gcc -m32" CXX="g++ -m32" CFLAGS="-g -O2 -msse2 -D_GNU_SOURCE -DNDEBUG -DITIMER_HEARTBEAT=1 -DNO_VM_PROFILE=1 -DCOGMTVM=0" LIBS=-lpthread
 To run a 32-bit VM on a 64-bit OS, you'll also need the 32-bit libraries
 provided by the ia32-libs package.
+
+
+According to Paul DeBruicker  the following packages need to be installed to
+compile in 32-bt mode on 64-bit ubuntu.  YMMV.
+
+lib32asound2-dev
+libgl1-mesa-dev
+libglu1-mesa-dev
+build-essential
+ia32-libs
+gcc-multilib
+g++multilib