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