class library: Volume - remove debug message
[supercollider.git] / SCClassLibrary / Common / Core / Object.sc
blob3661678279c7b8e23dcc8f75df4156962e978ac8
1 Object  {
2         classvar <dependantsDictionary, currentEnvironment, topEnvironment, <uniqueMethods;
4         const nl = "\n";
6         *new { arg maxSize = 0;
7                 _BasicNew
8                 ^this.primitiveFailed
9                 // creates a new instance that can hold up to maxSize
10                 // indexable slots. the indexed size will be zero.
11                 // to actually put things in the object you need to
12                 // add them.
13         }
14         *newCopyArgs { arg ... args;
15                 _BasicNewCopyArgsToInstVars
16                 ^this.primitiveFailed
17                 // creates a new instance that can hold up to maxSize
18                 // indexable slots. the indexed size will be zero.
19                 // to actually put things in the object you need to
20                 // add them.
21         }
23         // debugging and diagnostics
24         dump { _ObjectDump }
25         post { this.asString.post }
26         postln { this.asString.postln; }
27         postc { this.asString.postc }
28         postcln { this.asString.postcln; }
29         postcs { this.asCompileString.postln }
30         totalFree { _TotalFree }
31         largestFreeBlock { _LargestFreeBlock }
32         gcDumpGrey { _GCDumpGrey }
33         gcDumpSet { arg set; _GCDumpSet }
34         gcInfo { _GCInfo }
35         gcSanity { _GCSanity }
36         canCallOS { _CanCallOS }
39         //accessing
40         size { ^0 }
41         indexedSize { ^0 }
42         flatSize { ^1   }
44         do { arg function; function.value(this, 0) }
45         generate { arg function, state; this.do(function); ^state }
46         //reverseDo { arg function; function.value(this, 0) }
48         // class membership
49         class { _ObjectClass; ^this.primitiveFailed }
50         isKindOf { arg aClass; _ObjectIsKindOf; ^this.primitiveFailed }
51         isMemberOf { arg aClass; _ObjectIsMemberOf; ^this.primitiveFailed }
52         respondsTo { arg aSymbol; _ObjectRespondsTo; ^this.primitiveFailed }
54         performMsg { arg msg;
55                 _ObjectPerformMsg;
56                 ^this.primitiveFailed
57         }
59         perform { arg selector ... args;
60                 _ObjectPerform;
61                 ^this.primitiveFailed
62         }
63         performList { arg selector, arglist;
64                 _ObjectPerformList;
65                 ^this.primitiveFailed
66         }
67         functionPerformList {
68                 // perform only if Function. see Function-functionPerformList
69                 ^this
70         }
72         // super.perform(selector,arg) doesn't do what you might think.
73         // \perform would be looked up in the superclass, not the selector you are interested in.
74         // Hence these methods, which look up the selector in the superclass.
75         // These methods must be called with this as the receiver.
76         superPerform { arg selector ... args;
77                 _SuperPerform;
78                 ^this.primitiveFailed
79         }
80         superPerformList { arg selector, arglist;
81                 _SuperPerformList;
82                 ^this.primitiveFailed
83         }
85         tryPerform { arg selector ... args;
86                 ^if(this.respondsTo(selector),{
87                         this.performList(selector,args)
88                 })
89         }
90         multiChannelPerform { arg selector ... args;
91                 ^flop([this, selector] ++ args).collect { |item|
92                         performList(item[0], item[1], item[2..])
93                 }
94         }
96         performWithEnvir { |selector, envir|
97                 var argNames, args;
98                 var method = this.class.findRespondingMethodFor(selector);
99                 
100                 if(method.isNil) { ^this.doesNotUnderstand(selector) };
101                 
102                 argNames = method.argNames.drop(1);
103                 args = method.prototypeFrame.drop(1);
104                 argNames.do { |name, i|
105                         var val = envir[name];
106                         val !? { args[i] = val };
107                 };
108                 
109                 ^this.performList(selector, args)
110         }
112         performKeyValuePairs { |selector, pairs|
113                 ^this.performWithEnvir(selector, ().putPairs(pairs))
114         }
116         // copying
117         copy { ^this.shallowCopy }
118         contentsCopy { ^this.shallowCopy }
119         shallowCopy { _ObjectShallowCopy; ^this.primitiveFailed }
120         copyImmutable {
121                 // if object is immutable then return a shallow copy, else return receiver.
122                 _ObjectCopyImmutable;
123                 ^this.primitiveFailed
124         }
126         deepCopy {
127                 _ObjectDeepCopy
128                 ^this.primitiveFailed
129         }
130         dup { arg n = 2;
131                 ^Array.fill(n, { this.copy });
132         }
133         ! { arg n;
134                 ^this.dup(n)
135         }
137         // evaluation
138         poll { ^this.value }
139         value { ^this }
140         valueArray { ^this }
141         valueEnvir { ^this }
142         valueArrayEnvir { ^this }
144         // equality, identity
145         == { arg obj; ^this === obj }
146         != { arg obj; ^not(this == obj) }
147         === { arg obj; _Identical; ^this.primitiveFailed }
148         !== { arg obj;_NotIdentical; ^this.primitiveFailed }
149         equals { arg that, properties;
150                 ^that.respondsTo(properties) and: {
151                         properties.every { |selector| this.perform(selector) == that.perform(selector) }
152                 }
153         }
154         compareObject { arg that, instVarNames;
155                 if(this === that,{ ^true });
156                 // possibly ok if one of us isKindOf the other
157                 if(this.class !== that.class,{ ^false });
158                 if(instVarNames.notNil,{
159                         instVarNames.do({ |varname|
160                                 if(this.instVarAt(varname) != that.instVarAt(varname),{
161                                         ^false
162                                 })
163                         });
164                 },{
165                         this.instVarSize.do({ arg i;
166                                 if(this.instVarAt(i) != that.instVarAt(i),{ ^false });
167                         });
168                 });
169                 ^true
170         }
171         instVarHash { arg instVarNames;
172                 var indices, res = this.class.hash;
173                 if(this.instVarSize == 0) {
174                         ^res
175                 };
176                 indices = if(instVarNames.notNil) {
177                         instVarNames.collect(this.slotIndex(_))
178                 } {
179                         (0..this.instVarSize-1)
180                 };
181                 indices.do { |i|
182                         var obj = this.instVarAt(i);
183                         res = res << 1 bitXor: obj.hash;  // encode slot order by left shifting
184                 };
185                 ^res
186         }
188         basicHash { _ObjectHash; ^this.primitiveFailed }
189         hash { _ObjectHash; ^this.primitiveFailed }
190         identityHash { _ObjectHash; ^this.primitiveFailed }
192         // create an association
193         -> { arg obj; ^Association.new(this, obj) }
195         // stream
196         next { ^this }
197         reset { ^this }
198         first { arg inval; this.reset; ^this.next(inval) }
199         iter { ^OneShotStream(this) }
200         stop { ^this }
201         free { ^this }
202         clear { ^this }
203         removedFromScheduler { ^this }
204         isPlaying { ^false }
205         embedInStream { ^this.yield; }
206         cyc { arg n = inf;
207                 ^r {|inval|
208                         n.do {
209                                 inval = this.embedInStream(inval);
210                                 this.reset;
211                         }
212                 }
213         }
214         fin { arg n = 1;
215                 ^r {|inval|
216                         var item;
217                         n.do {
218                                 item = this.next(inval);
219                                 if (item.isNil) { nil.alwaysYield };
220                                 inval = item.yield
221                         }
222                 }
223         }
225         repeat { arg repeats = inf; ^Pn(this, repeats).asStream }
226         loop { ^this.repeat(inf) }
228         asStream { ^this }
230         eventAt { ^nil }
231         composeEvents { arg event; ^event.copy }
233         finishEvent {}
234         atLimit { ^false }
236         isRest { ^false }
238         threadPlayer {}
239         threadPlayer_ {}
241         // testing
242         ? { arg obj; ^this }
243         ?? { arg obj; ^this }
244         !? { arg obj; ^obj.value(this) }
246         isNil { ^false }
247         notNil { ^true }
248         isNumber { ^false }
249         isInteger { ^false }
250         isFloat { ^false }
251         isSequenceableCollection { ^false }
252         isCollection { ^false }
253         isArray { ^false }
254         isString { ^false }
255         containsSeqColl { ^false }
256         isValidUGenInput { ^false }
257         isException { ^false }
258         isFunction { ^false }
260         matchItem {|item| ^this === item }
261         trueAt { ^false }
262         falseAt { arg key;
263                 ^this.trueAt(key).not
264         }
266         pointsTo { arg obj; _ObjectPointsTo; ^this.primitiveFailed }
267         mutable { _ObjectIsMutable; ^this.primitiveFailed }
268         frozen { _ObjectIsPermanent; ^this.primitiveFailed }
270         // errors
271         halt {
272                 thisProcess.nowExecutingPath = nil;
273                 OnError.run;
274                 this.prHalt
275         }
276         prHalt { _Halt }
277         primitiveFailed {
278                 PrimitiveFailedError(this).throw;
279         }
280         reportError {
281                 error(this.asString);
282                 this.dumpBackTrace;
283         }
285         subclassResponsibility { arg method;
286                 SubclassResponsibilityError(this, method, this.class).throw;
287         }
288         doesNotUnderstand { arg selector ... args;
289                 DoesNotUnderstandError(this, selector, args).throw;
290         }
291         shouldNotImplement { arg method;
292                 ShouldNotImplementError(this, method, this.class).throw;
293         }
294         outOfContextReturn { arg method, result;
295                 OutOfContextReturnError(this, method, result).throw;
296         }
297         immutableError { arg value;
298                 ImmutableError(this, value).throw;
299         }
301         deprecated { arg method, alternateMethod;
302                 DeprecatedError(this, method, alternateMethod, this.class).throw;
303         }
305         mustBeBoolean { MustBeBooleanError(nil, this).throw; }
306         notYetImplemented { NotYetImplementedError(nil, this).throw; }
308         dumpBackTrace { _DumpBackTrace }
309         getBackTrace { _GetBackTrace }
310         throw {
311                 if (Error.handling) {
312                         error("throw during error handling!\n");
313                         this.dump;
314                         ^this
315                 };
316                 thisThread.handleError(this);
317         }
320         // conversion
321         species { ^this.class }
322         asCollection { ^[this] }
323         asSymbol { ^this.asString.asSymbol }
324         asString { arg limit = 512;
325                 var string;
326                 _ObjectString
327                 string = String.streamContentsLimit({ arg stream; this.printOn(stream); }, limit);
328                 if (string.size >= limit, { ^(string ++ "...etc..."); });
329                 ^string
330         }
331         asCompileString {
332                 _ObjectCompileString
333                 ^String.streamContents({ arg stream; this.storeOn(stream); });
334         }
336         cs { ^this.asCompileString }
338         printClassNameOn { arg stream;
339                 var title;
340                 title = this.class.name.asString;
341                 stream << if((title @ 0).isVowel, { "an " }, { "a " }) << title;
342         }
343         printOn { arg stream;
344                 this.printClassNameOn(stream);
345         }
346         storeOn { arg stream;
347                 stream << this.class.name;
348                 this.storeParamsOn(stream);
349                 this.storeModifiersOn(stream);
350         }
351         storeParamsOn { arg stream;
352                 var args = this.storeArgs;
353                 if(args.notEmpty) {
354                         stream << "(" <<<* this.simplifyStoreArgs(args) << ")";
355                 } {
356                         stream << ".new"
357                 }
358         }
359         simplifyStoreArgs { arg args;
360                 var res = Array.new, newMethod, methodArgs;
361                 newMethod = this.class.class.findRespondingMethodFor(\new);
362                 methodArgs = newMethod.prototypeFrame.drop(1);
363                 args.size.reverseDo { |i|
364                         if(methodArgs[i] != args[i]) {
365                                 ^args.keep(i + 1)
366                         }
367                 }
368                 ^[]
369         }
370         storeArgs { ^#[] }
371         storeModifiersOn { arg stream;}
374         as { arg aSimilarClass; ^aSimilarClass.newFrom(this) }
375         dereference { ^this } // see Ref::dereference
376         reference { ^Ref.new(this) }
377         asRef { ^Ref.new(this) }
378         // asArray { ^Array.with(this) }
379         asArray { ^this.asCollection.asArray }
380         asSequenceableCollection { ^this.asArray }
382         // arrays
383         rank { ^0 }
384         deepCollect { arg depth, function, index = 0, rank = 0; ^function.value(this, index, rank) }
385         deepDo { arg depth, function, index = 0, rank = 0; function.value(this, index, rank) }
386         slice { ^this }
387         shape { ^nil }
388         unbubble { ^this }
389         bubble { arg depth=0, levels=1;
390                 if (levels <= 1) { ^[this] };
391                 ^[this.bubble(depth,levels-1)]
392         }
394         // compatibility with sequenceable collection
396         obtain { arg index, default;  ^if(index == 0) { this } { default } }
398         instill { arg index, item, default;
399                 ^if(index == 0) { item } {
400                         this.asArray.instill(index, item, default)
401                 }
402         }
404         // FunctionList support
405         addFunc { arg ... functions;
406                 ^FunctionList([this] ++ functions)
407         }
408         removeFunc { arg function; if(this === function) { ^nil } }
409         replaceFunc { arg find, replace; if(this === find) { ^replace } }
410         addFuncTo { arg variableName ... functions;
411                 this.perform(variableName.asSetter, this.perform(variableName).addFunc(*functions))
412         }
413         removeFuncFrom { arg variableName, function;
414                 this.perform(variableName).removeFunc(function)
415         }
417         // looping
418         while { arg body;
419                 // compiler magic: the compiler inlines the following loop
420                 // thus an uninlinable while can be implemented using while itself
421                 while({ this.value }, {
422                         body.value
423                 });
424         }
425         switch { arg ... cases;
426                 cases.pairsDo { | test, trueFunc |
427                         if (this == test.value) { ^trueFunc.value };
428                 };
429                 if (cases.size.odd) { ^cases.last.value };
430                 ^nil
431         }
433         // coroutine support
434         yield {
435                 _RoutineYield
436                 ^this.primitiveFailed
437         }
438         alwaysYield {
439                 _RoutineAlwaysYield
440                 ^this.primitiveFailed
441         }
442         yieldAndReset { arg reset = true;
443                 _RoutineYieldAndReset
444                 ^this.primitiveFailed
445         }
446         idle { arg val;
447                 var time = thisThread.beats;
448                 while { thisThread.beats - time < val } { this.value.yield }
449         }
451         // dependancy support
452         *initClass { dependantsDictionary = IdentityDictionary.new(4); }
453         dependants {
454                 ^dependantsDictionary.at(this) ?? { IdentitySet.new };
455         }
456         changed { arg what ... moreArgs;
457                 dependantsDictionary.at(this).copy.do({ arg item;
458                         item.update(this, what, *moreArgs);
459                 });
460         }
461         addDependant { arg dependant;
462                 var theDependants;
463                 theDependants = dependantsDictionary.at(this);
464                 if(theDependants.isNil,{
465                         theDependants = IdentitySet.new.add(dependant);
466                         dependantsDictionary.put(this, theDependants);
467                 },{
468                         theDependants.add(dependant);
469                 });
470         }
471         removeDependant { arg dependant;
472                 var theDependants;
473                 theDependants = dependantsDictionary.at(this);
474                 if (theDependants.notNil, {
475                         theDependants.remove(dependant);
476                         if (theDependants.size == 0, {
477                                 dependantsDictionary.removeAt(this);
478                         });
479                 });
480         }
481         release {
482                 this.releaseDependants;
483         }
484         releaseDependants {
485                 dependantsDictionary.removeAt(this);
486         }
487         update { arg theChanged, theChanger;    // respond to a change in a model
488         }
491         // instance specific method support
492         addUniqueMethod { arg selector, function;
493                 var methodDict;
494                 if(function.isKindOf(Function).not) {
495                         Error("A method must be defined using a function").throw
496                 };
497                 if(uniqueMethods.isNil, { uniqueMethods = IdentityDictionary.new });
498                 methodDict = uniqueMethods.at(this);
499                 if (methodDict.isNil, {
500                         methodDict = IdentityDictionary.new;
501                         uniqueMethods.put(this, methodDict);
502                 });
503                 methodDict.put(selector, function);
504         }
505         removeUniqueMethods {
506                 if (uniqueMethods.notNil, {
507                         uniqueMethods.removeAt(this);
508                 });
509         }
510         removeUniqueMethod { arg selector;
511                 var methodDict;
512                 if (uniqueMethods.notNil, {
513                         methodDict = uniqueMethods.at(this);
514                         if (methodDict.notNil, {
515                                 methodDict.removeAt(selector);
516                                 if (methodDict.size < 1, {
517                                         uniqueMethods.removeAt(this);
518                                 });
519                         });
520                 });
521         }
523         inspect { ^this.inspectorClass.new(this) }
524         inspectorClass { ^ObjectInspector }
525         inspector {
526                 // finds the inspector for this object, if any.
527                 ^Inspector.inspectorFor(this)
528         }
531         // virtual machine debugging...
532         crash { _HostDebugger } // for serious problems..
533         stackDepth { _StackDepth }
534         dumpStack { _DumpStack }
535         dumpDetailedBackTrace { _DumpDetailedBackTrace }
538         freeze {
539                 _ObjectDeepFreeze
540                 ^this.primitiveFailed
541         }
543         // Math protocol support
544         // translate these operators to names the code generator can safely generate in C++
545         & { arg that; ^bitAnd(this, that) }
546         | { arg that; ^bitOr(this, that) }
547         % { arg that; ^mod(this, that) }
548         ** { arg that; ^pow(this, that) }
549         << { arg that; ^leftShift(this, that) }
550         >> { arg that; ^rightShift(this, that) }
551         +>> { arg that; ^unsignedRightShift(this, that) }
552         <! { arg that; ^firstArg(this, that) }
554         asInt { ^this.asInteger }
556         blend { arg that, blendFrac = 0.5;
557                 // blendFrac should be from zero to one
558                 ^this + (blendFrac * (that - this));
559         }
561         blendAt { arg index, method='clipAt';
562                 var iMin = index.roundUp.asInteger - 1;
563                 ^blend(this.perform(method, iMin), this.perform(method, iMin+1), absdif(index, iMin));
564         }
566         blendPut { arg index, val, method='wrapPut';
567                 var iMin = index.floor.asInteger;
568                 var ratio = absdif(index, iMin);
569                 this.perform(method, iMin, val * (1-ratio));
570                 this.perform(method, iMin + 1, val * ratio);
571         }
574         fuzzyEqual { arg that, precision=1.0; ^max(0.0, 1.0 - (abs(this - that)/precision)) }
576         isUGen { ^false }
577         numChannels { ^1 }
579         pair { arg that; ^[this, that] }
580         pairs { arg that;
581                 var list;
582                 list = [];
583                 this.asArray.do {|a|
584                         that.asArray.do {|b|
585                                 list = list.add(a.asArray ++ b)
586                         };
587                 };
588                 ^list;
589         }
592         // scheduling
593         awake { arg beats, seconds, clock;
594                 var time;
595                 time = seconds; // prevent optimization
596                 ^this.next(beats)
597         }
598         beats_ {  } // for PauseStream
599         clock_ {  } // for Clock
601         // catch binary operators failure
602         performBinaryOpOnSomething { arg aSelector, thing, adverb;
603                 if (aSelector === '==', {
604                         ^false
605                 },{
606                 if (aSelector === '!=', {
607                         ^true
608                 },{
609                         BinaryOpFailureError(this, aSelector, [thing, adverb]).throw;
610                 })});
611         }
612         performBinaryOpOnSimpleNumber { arg aSelector, thing, adverb;
613                 ^this.performBinaryOpOnSomething(aSelector, thing, adverb)
614         }
615         performBinaryOpOnSignal { arg aSelector, thing, adverb;
616                 ^this.performBinaryOpOnSomething(aSelector, thing, adverb)
617         }
618         performBinaryOpOnComplex { arg aSelector, thing, adverb;
619                 ^this.performBinaryOpOnSomething(aSelector, thing, adverb)
620         }
621         performBinaryOpOnSeqColl { arg aSelector, thing, adverb;
622                 ^this.performBinaryOpOnSomething(aSelector, thing, adverb)
623         }
624         performBinaryOpOnUGen { arg aSelector, thing, adverb;
625                 ^this.performBinaryOpOnSomething(aSelector, thing, adverb)
626         }
628         writeDefFile { arg name, dir, overwrite = (true);
630                 StartUp.defer { // make sure the synth defs are written to the right path
631                         var file;
632                         dir = dir ? SynthDef.synthDefDir;
633                         if (name.isNil) { Error("missing SynthDef file name").throw } {
634                                 name = dir +/+ name ++ ".scsyndef";
635                                 if(overwrite or: { pathMatch(name).isEmpty })
636                                         {
637                                         file = File(name, "w");
638                                         protect {
639                                                 AbstractMDPlugin.clearMetadata(name);
640                                                 this.asArray.writeDef(file);
641                                         }{
642                                                 file.close;
643                                         }
644                                 }
645                         }
646                 }
648         }
650         isInputUGen { ^false }
651         isOutputUGen { ^false }
652         isControlUGen { ^false }
653         source { ^this }
654         asUGenInput { ^this }
655         asControlInput { ^this }
656         asAudioRateInput { ^if(this.rate != \audio) { K2A.ar(this) } { this } }
659         // these are the same as new and newCopyArgs, but should not be overridden by any class.
660         *prNew { arg maxSize = 0;
661                 _BasicNew
662                 ^this.primitiveFailed
663                 // creates a new instance that can hold up to maxSize
664                 // indexable slots. the indexed size will be zero.
665                 // to actually put things in the object you need to
666                 // add them.
667         }
668         *prNewCopyArgs { arg ... args;
669                 _BasicNewCopyArgsToInstVars
670                 ^this.primitiveFailed
671                 // creates a new instance which holds the args as slots
672         }
674         //////
675         // these are dangerous operations as they break encapsulation and
676         // can allow access to slots that should not be accessed because they are private to the
677         // virtual machine, such as Frame objects.
678         // Use with caution.
679         // see counterparts to these in ArrayedCollection
680         slotSize {
681                 ^this.instVarSize;
682         }
683         slotAt { arg index;
684                 // index can be an integer or symbol.
685                 ^this.instVarAt(index);
686         }
687         slotPut { arg index, value;
688                 // index can be an integer or symbol.
689                 ^this.instVarPut(index, value);
690         }
691         slotKey { arg index;
692                 // index must be an integer.
693                 ^this.class.instVarNames.at(index)
694         }
695         slotIndex { arg key;
696                 // key must be a symbol.
697                 ^this.class.instVarNames.indexOf(key)
698         }
699         slotsDo { arg function;
700                 this.slotSize.do {|i|
701                         function.value(this.slotKey(i), this.slotAt(i), i);
702                 };
703         }
704         slotValuesDo { arg function;
705                 this.slotSize.do {|i|
706                         function.value(this.slotAt(i), i);
707                 };
708         }
710         // getSlots and setSlots will be used for a new implementation of asCompileString.
711         // getSlots stores the keys and values so that if the instance
712         // variable order changes, setSlots they will still set the right one.
713         getSlots {
714                 var array;
715                 array = Array.new(this.slotSize * 2);
716                 this.slotSize.do {|i|
717                         array.add(this.slotKey(i));
718                         array.add(this.slotAt(i));
719                 };
720                 ^array;
721         }
722         setSlots { arg array;
723                 array.pairsDo {|key, value|
724                         this.slotPut(key, value);
725                 }
726         }
728         instVarSize { _InstVarSize; ^this.primitiveFailed }
729         instVarAt { arg index;
730                 // index can be an integer or symbol.
731                 _InstVarAt;
732                 ^this.primitiveFailed;
733         }
734         instVarPut { arg index, item;
735                 // index can be an integer or symbol.
736                 _InstVarPut;
737                 ^this.primitiveFailed;
738         }
740         //////////// ARCHIVING ////////////
742         writeArchive { arg pathname;
743                 ^this.writeTextArchive(pathname)
744         }
745         *readArchive { arg pathname;
746                 ^this.readTextArchive(pathname)
747         }
748         asArchive {
749                 ^this.asTextArchive;
750         }
752         initFromArchive {}
754         archiveAsCompileString { ^false }
755         archiveAsObject { ^this.archiveAsCompileString.not }
756         checkCanArchive {}
758         // archiving
759         writeTextArchive { arg pathname;
760                 var text = this.asTextArchive;
761                 var file = File(pathname, "w");
762                 if(file.isOpen) {
763                         protect {
764                                 file.write(text);
765                         } { file.close };
766                 } {
767                         MethodError("Could not open file % for writing".format(pathname.asCompileString), this).throw;
768                 }
769         }
770         *readTextArchive { arg pathname;
771                 ^pathname.load
772         }
773         asTextArchive {
774                 var objects, list, stream, firsttime = true;
776                 if (this.archiveAsCompileString) {
777                         this.checkCanArchive;
778                         ^this.asCompileString ++ "\n"
779                 };
781                 objects = IdentityDictionary.new;
783                 this.getContainedObjects(objects);
785                 stream = CollStream.new;
786                 stream << "var o, p;\n";
788                 list = List.newClear(objects.size);
789                 objects.keysValuesDo {|obj, index| list[index] = obj };
791                 stream << "o = [";
792                 list.do {|obj, i|
793                         var size;
794                         if (i != 0) { stream << ",  "; };
795                         if ((i & 3) == 0) { stream << "\n\t" };
796                         obj.checkCanArchive;
797                         if (obj.archiveAsCompileString) {
798                                 stream << obj.asCompileString;
799                         }{
800                                 size = obj.indexedSize;
801                                 stream << obj.class.name << ".prNew";
802                                 if (size > 0) {
803                                         stream << "(" << size << ")"
804                                 };
805                         };
806                 };
807                 stream << "\n];\np = [";
808                 // put in slots
809                 firsttime = true;
810                 list.do {|obj, i|
811                         var slots;
812                         if (obj.archiveAsCompileString.not) {
813                                 slots = obj.getSlots;
814                                 if (slots.size > 0) {
815                                         if (firsttime.not) { stream << ",  "; };
816                                         firsttime = false;
817                                         stream << "\n\t// " << obj.class.name;
818                                         stream << "\n\t";
819                                         stream << i << ", [ ";
820                                         if (obj.isKindOf(ArrayedCollection)) {
821                                                 slots.do {|slot, j|
822                                                         var index;
823                                                         if (j != 0) { stream << ",  "; };
824                                                         if ((j != 0) && ((j & 3) == 0)) { stream << "\n\t\t" };
825                                                         index = objects[slot];
826                                                         if (index.isNil) {
827                                                                 stream << slot.asCompileString;
828                                                         }{
829                                                                 stream << "o[" << index << "]";
830                                                         };
831                                                 };
832                                         }{
833                                                 slots.pairsDo {|key, slot, j|
834                                                         var index;
835                                                         if (j != 0) { stream << ",  "; };
836                                                         if ((j != 0) && ((j & 3) == 0)) { stream << "\n\t\t" };
837                                                         stream << key << ": ";
838                                                         index = objects[slot];
839                                                         if (index.isNil) {
840                                                                 stream << slot.asCompileString;
841                                                         }{
842                                                                 stream << "o[" << index << "]";
843                                                         };
844                                                 };
845                                         };
846                                         stream << " ]";
847                                 };
848                         };
849                 };
850                 stream << "\n];\n";
852                 stream << "prUnarchive(o,p);\n";
853                 ^stream.contents
854         }
855         getContainedObjects { arg objects;
856                 if (objects[this].notNil) {^this};
857                 objects[this] = objects.size;
859                 if (this.archiveAsCompileString.not) {
860                         this.slotsDo {|key, slot|
861                                 if (slot.archiveAsObject) {
862                                         slot.getContainedObjects(objects);
863                                 };
864                         };
865                 };
867         }
868         // old binary archiving
869         // this will break if the instance vars change !
870         // not recommended
871         writeBinaryArchive { arg pathname;
872                 _WriteArchive
873                 ^this.primitiveFailed;
874         }
875         *readBinaryArchive { arg pathname;
876                 _ReadArchive
877                 ^this.primitiveFailed;
878         }
879         asBinaryArchive {
880                 _AsArchive
881                 ^this.primitiveFailed;
882         }
883         // support for Gen
884         genNext { ^nil }
885         genCurrent { ^this }
887         // support for ViewRedirect
888         *classRedirect { ^this }
890         help {
891                 this.class.asString.help
892         }