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