To: herring@pike.cecer.army.mil In-reply-to: <199411301711.LAA18301@pike.cecer.army.mil> (message from Charles Herring on Wed, 30 Nov 1994 11:10:16 -0600 (CST)) Subject: Re: Hexagonal CAs Reply-to: hpm@cs.cmu.edu FCC: ~/Mail/MAILOUT --text follows this line-- The program following uses Macintosh graphics, whose intent should be roughly obvious. It is very efficient, using two main tricks. It updates 8 cells at one time. In parallel, using 32 bit logical operations, it constructs the 16 bit neighborhoods of a row of four bits n n n n n n * * * * n n n n n n for two neighborhoods in parallel, then looks up the new state of each set of four bits by two accesses into a 2^16 byte table constructed from the rule. One version of the function maintains a linked list of all the active areas, and updates only those words whose neighborhoods have changed, relinking for the next generation as it goes along. The space is the simplest to implement toroid, with a one line jog at wraparound. Here's an old note describing the good rule (others have interesting properties too, though): I started fooling around with the hexlife program again, and tried a few more mutations and matings of plausible black/white symmetric rules, and stumbled on a family that had promising properties - gliders on the one hand, and a tendency to consolidate like colored areas on the other. A few tweaks of the genome produced the first really interesting candidate: (00(-+0)(+--)(-+1)11) This is a totally (rotation, reflection, color inversion) symmetric rule that has at least three weights of gliders, several simple period two oscilators, and a moderately chaotic boundary between black and white areas that, slowly, chews away at convexities, and so evaporates small regions of one color surrounded by the other. When I initialized my appoximately 400 by 600 toroidal screen to half black, half white, with a splotch of randomization in the middle, the pattern meandered around for about 100,000 generations, looking a lot like a cloudy night sky, with white twinkling stars (and shooting star gliders) showing in the black sky between the white clouds. Of course there were twinkling black stars in the white clouds also. The clouds billowed around, holding their 50% initialization pretty well, and coalescing until about 50K generations, then black got an edge, and soon there was a single white cloud surrounded by encroaching black, which gradually ate it all away, leaving a handful of (toroidally) circulating gliders, and blinkers. (Most glider and blinker collisions leave no debris.) So I thought, neither color can win if I make the initial pattern perfectly symmetric. I started the screen top half white, bottom half black. Initially this produced a lightspeed shock wave of alternating (in time and space) black and white lines. But these gradually got eaten by chaos from the edges (my toroid has a one scanline vertical skew from right to left edge, making a dislocation). Then a lot of cloud cover, with gradual coalescence, eventually to a meandering vertical boundary, with left half of screen black and right half white, with the churning boundary occasionally yin/yanging (in the middle, and also around the left/right wraparound), but averaging straight. I guess it likes vertical over horizontal because that minimizes boundary length in my rectangular world - only 400 pixels in a vertical line, to 600 in a horizontal one. On the torus there are 4 points of symmetry, one in the middle of the screen, one at middle top and bottom, one at middle left and right, and one at the four corners. By global symmetry the black/white boundary is constrained to run through those points, you can almost see the nails holding it down there. The color boundary looks like a really long period pseudo random generator, frothing, spitting out flecks of foam that usually evaporate, but sometimes leave a blinker or a glider that crosses its background color until it plunges inth th boundary from the other side. Gliders, of course, can't pass the boundary from one color to another, they just add to the froth. Glider collisions sometimes produce temporary structures in between the boundary, including an occasional bilaterally symmetric structure that looks like a dynamic totem pole that sprouts wings and faces for several hundered generations before evaporating. There seem to be no stationary patterns. Simple period two oscillators: * * * * * * * * <- hexagon to star of david and back * * A period thirty oscillator! : * * * * * * * * * * * * Big Hexagon, star of david, 28 beautiful snowflakes * * * * * * * The notation in the rule above encodes neighborhood by position, and in each position indicates, for that neighborhood, 1: always set the cell to one 0: always set the cell to zero +: keep the cell in its former state -: toggle the cell to the opposite of its former state The positions in the rule refer to the following neighborhoods (each with all its rotations and reflections): 00 00 01 10 00 11 01 10 11 11 01 11 11 (0 0 0 1 (0 1 0 1 1 1)(0 1 1 1 0 1)(1 1 0 1 1 1) 1 1 1 1) 00 00 00 00 00 00 00 10 00 10 10 10 11 Here's that rule again: (00(-+0)(+--)(-+1)11) ----------------------------------------------------------------------------- Other rules of interest: hexlife (00(1+0)(---)(000)00) /* clean smoke */ (00(1+0)(0-+)(++0)10) (00(1+0)(0-+)(+++)10) (00(1+0)(0-+)(++0)1+) (00(1+0)(0-+)(+00)11) (00(1+0)(0(-1)+)(+++)++) (00(1+0)(0-+)(++0)1+) (00(1+0)(0-+)(++0)+1) (00(1+0)(0-+)(++0)+1) /* modest smoker */ (00(1+0)(0-+)(++0)1+) (00(1+0)(0-+)(++1)+1) /* many gliders, smokers, wigglers, shapes - self limiting*/ /* Very "Life"-like !!!! */ (00(1++)0000) /* too sparse? */ (00(11+)0000) /* too vigorous */ /* Life Similar - has glider */ (00(1+0)(0-+)(++0)11) /* grows slow */ (00(1+0)(0-+)(+++)11) /* grows slow */ (00(1+0)(0-+)(++1)11) /* grows slightly less slow */ (00(1+0)(0-+)(++-)11) /* grows slightly faster */ (00(1+0)(0(-1)+)(+++)1+) /* slightly faster */ (00(1+0)(0(-1)+)(+++)11) /* slightly faster */ (00(1+0)(0(-+)+)(+0+)11) /* dies very fast */ (00(1+0)(0(-+)+)(0++)11) /* dies very fast */ (00(1+0)(0-+)(++0)-1) /* dies very fast */ /* slowly builds black island */ (00(1+0)(0(-+)+)(+++)11) /* slowly unbuilds black island */ (00(1+0)(0-+)(01+)11) /* Makes Rays */ -- Hans From hpm Thu May 26 23:09:57 -0400 1994 To: gennery@bryce.jpl.nasa.gov cc: hpm In-reply-to: <199405220550.WAA08610@bryce.jpl.nasa.gov> (message from Donald Gennery on Sat, 21 May 1994 22:50:07 -0700) Subject: hexlife.c Reply-to: hpm@cs.cmu.edu #define RULE "(00(-+0)(+--)(-+1)11)" #define LW32 19 #define LW (LW32*32) #define LH 402 #define LS32 (LW32*LH) #define DLW32 (LW32*2) #define TLW32 (LW32*3) #define LRratio 62 /* speed per active word of linked/raw versions, as percent */ #include #include #include #include #include #include #include #include #include #include #include char ln[200]; BitMap BM1; Rect BMB, BMR, WMR; char equiv[64], equivcnt[64], rules[128], bitcnt[128]; unsigned char *rule4; unsigned int *cell, *cxor; int *link; int MaxX, MaxY; extern WindowPtr graphicWindow; int Toroid=1; /* Does the cell array wrap around? */ TableInit() /* set up rotation and reflection equivalence tables */ {int i, j, k, l, n; for (i=0; i<128; ++i) {n=0; for (j=1; j<=0100; j *= 2) if ((j&i)!=0) ++n; bitcnt[i]=n;} /* calculate pattern equivalence classes - rotation and reflection */ for (i=0; i<64; ++i) equiv[i] = -1; n=0; for (i=0; i<64; ++i) if (equiv[i]<0) {j=i; ++n; for (k=0; k<1; ++k) /* to k<2 if reflection symmetry required */ {for (l=0; l<6; ++l) {if (equiv[j]<0) {equivcnt[i]++; equiv[j] = i;} else if (equiv[j]!=i) printf("Glitch at %o, %o, (%o)\n",i,j,equiv[j]); j = (j&037)<<1 | (j&040)>>5; } j = (j&060)>>4 | (j&03)<<4 | (j&014); /* reflection */ j = (j&052)>>1 | (j&025)<<1; } } } st(pat,key) int pat; char key; /* set neighborhood pat to code key */ {int make, keep, i; if (key=='0') make=keep=0; else if (key=='1') make=keep=1; else if (key=='+') {make=0; keep=1;} else if (key=='-') {make=1; keep=0;} else return(0); pat = equiv[((pat/10)%10)*8 + pat%10]; for (i=0; i<64; ++i) if (equiv[i]==pat) {rules[i]=make; rules[i+64]=keep;} return(1); } char rc(pat) int pat; /* return code for transition rule with neighborhood pat */ {int t; t = (pat/10)*8 + pat%10; /* undo decimal conversion */ return("0-+1"[(rules[0100|t]<<1) | rules[t]]); } int MakeRule(defline) char *defline; /* Parse the transformation rule */ {int i, j, k, l, c; for (i=0; i<128; ++i) rules[i]=0; if((*defline++)!='(') return(0); if(!st(0,*defline++) || !st(1,*defline++)) return(0); if((c=*defline++)=='(') {if(!st(3,*defline++) || !st(5,*defline++) || !st(11,*defline++) || (*defline++)!=')') return(0);} else {if(!st(3,c) || !st(5,c) || !st(11,c)) return(0);} if((c=*defline++)=='(') {if(!st(7,*defline++)) return(0); if((c=*defline++)=='(') {if(!st(13,*defline++) || !st(23,*defline++) || (*defline++)!=')') return(0);} else {if(!st(13,c) || !st(23,c)) return(0);} if(!st(25,*defline++) || (*defline++)!=')') return(0);} else {if(!st(7,c) || !st(13,c) || !st(23,c) || !st(25,c)) return(0);} if((c=*defline++)=='(') {if(!st(17,*defline++) || !st(27,*defline++) || !st(33,*defline++) || (*defline++)!=')') return(0);} else {if(!st(17,c) || !st(27,c) || !st(33,c)) return(0);} if(!st(37,*defline++) || !st(77,*defline++) || (*defline++)!=')') return(0); for (i=0; i<(1<<16); i++) /* set up table for 4 bits and neighborhood */ {c = 0; for (j=0; j<4; ++j) {k = i>>j; l = k&0x63; if(k&0x80) l |= 4; if(k&0x800) l |= 16; if(k&0x1000) l |= 8; c |= rules[l]<>6)&0xf); } return(1); /* hexagonal adjacencies: - 8 10 4 40 20 2 1 - */ } int CellTick() /* Update cell array */ {int llw; register int lw, t; unsigned int a, b, c, bit, w; int cnt; lw = link[llw=0]; while (lw>0) /* collect neighborhoods and compute changes */ {a = cell[lw-LW32]; b = cell[lw]; c = cell[lw+LW32]; w = (a&0xf800f800) | ((b>>6)&0x7e007e0) | ((c>>12)&0x1f001f); if (cell[lw-1]&1) w |= 0x4000000; if (cell[lw+LW32-1]&1) w |= 0x100000; bit = ((rule4[w>>16]<<16) | rule4[w&0xffff])<<12; w = ((a<<4)&0xf800f800) | ((b>>2)&0x7e007e0) | ((c>>8)&0x1f001f); bit |= ((rule4[w>>16]<<16) | rule4[w&0xffff])<<8; w = ((a<<8)&0xf800f800) | ((b<<2)&0x7e007e0) | ((c>>4)&0x1f001f); bit |= ((rule4[w>>16]<<16) | rule4[w&0xffff])<<4; w = ((a<<12)&0xf800f800) | ((b<<6)&0x7e007e0) | (c&0x1f001f); if (cell[lw+1]&0x80000000) w |= 0x20; if (cell[lw-LW32+1]&0x80000000) w |= 0x800; bit |= ((rule4[w>>16]<<16) | rule4[w&0xffff]); if(cxor[lw]=bit) lw=link[llw=lw]; else {link[llw]=lw=link[t=lw]; link[t]=0;}} lw = link[llw=0]; cnt=0; while (lw>0) /* apply changes, and link in neighbors */ {cnt++; cell[lw] ^= (w=cxor[lw]); if (!link[t=lw-LW32]) link[llw=link[llw]=t]=lw; if (!link[t=lw+LW32]) link[llw=link[llw]=t]=lw; if (w&1) {if (!link[t=lw-LW32+1]) link[llw=link[llw]=t]=lw; if (!link[t=lw+1]) link[llw=link[llw]=t]=lw; } if (w&0x80000000) {if (!link[t=lw+LW32-1]) link[llw=link[llw]=t]=lw; if (!link[t=lw-1]) link[llw=link[llw]=t]=lw; } lw = link[llw=lw];} return(cnt); } int CellTickToroid() /* Update cell array, with vertical wrap */ {int llw; register int lw, t; unsigned int A, B, C, bit, w; int p, n ,b, f, pf, nb, cnt; lw = link[llw=0]; while (lw>0) /* collect neighborhoods and compute changes */ {A = cell[lw-LW32]; B = cell[lw]; C = cell[lw+LW32]; w = (A&0xf800f800) | ((B>>6)&0x7e007e0) | ((C>>12)&0x1f001f); if (cell[lw-1]&1) w |= 0x4000000; if (cell[lw+LW32-1]&1) w |= 0x100000; bit = ((rule4[w>>16]<<16) | rule4[w&0xffff])<<12; w = ((A<<4)&0xf800f800) | ((B>>2)&0x7e007e0) | ((C>>8)&0x1f001f); bit |= ((rule4[w>>16]<<16) | rule4[w&0xffff])<<8; w = ((A<<8)&0xf800f800) | ((B<<2)&0x7e007e0) | ((C>>4)&0x1f001f); bit |= ((rule4[w>>16]<<16) | rule4[w&0xffff])<<4; w = ((A<<12)&0xf800f800) | ((B<<6)&0x7e007e0) | (C&0x1f001f); if (cell[lw+1]&0x80000000) w |= 0x20; if (cell[lw-LW32+1]&0x80000000) w |= 0x800; bit |= ((rule4[w>>16]<<16) | rule4[w&0xffff]); if(cxor[lw]=bit) lw=link[llw=lw]; else {link[llw]=lw=link[t=lw]; link[t]=0;}} lw = link[llw=0]; cnt=0; while (lw>0) /* apply changes, and link in neighbors */ {cnt++; t = (cell[lw] ^= (w=cxor[lw])); p = lw-LW32; n = lw+LW32; f = lw+1; b = lw-1; pf = p+1; nb = n-1; if(lw=LS32-DLW32) {n-=LS32-DLW32; cell[n-LW32]=t; if(lw!=LS32-DLW32) {nb-=LS32-DLW32; if(lw==LS32-LW32-1) f-=LS32-DLW32;}}; if (!link[p]) link[llw=link[llw]=p]=lw; if (!link[n]) link[llw=link[llw]=n]=lw; if (w&1) {if (!link[pf]) link[llw=link[llw]=pf]=lw; if (!link[f]) link[llw=link[llw]=f]=lw; } if (w&0x80000000) {if (!link[nb]) link[llw=link[llw]=nb]=lw; if (!link[b]) link[llw=link[llw]=b]=lw; } lw = link[llw=lw];} return(cnt); } int CellTickRaw() /* Update cell array, not using linked list */ {register int lw; unsigned int a, b, c, bit, w; int cnt; for (lw=LW32; lw= -1) {a = cell[lw-LW32]; b = cell[lw]; c = cell[lw+LW32]; w = (a&0xf800f800) | ((b>>6)&0x7e007e0) | ((c>>12)&0x1f001f); if (cell[lw-1]&1) w |= 0x4000000; if (cell[lw+LW32-1]&1) w |= 0x100000; bit = ((rule4[w>>16]<<16) | rule4[w&0xffff])<<12; w = ((a<<4)&0xf800f800) | ((b>>2)&0x7e007e0) | ((c>>8)&0x1f001f); bit |= ((rule4[w>>16]<<16) | rule4[w&0xffff])<<8; w = ((a<<8)&0xf800f800) | ((b<<2)&0x7e007e0) | ((c>>4)&0x1f001f); bit |= ((rule4[w>>16]<<16) | rule4[w&0xffff])<<4; w = ((a<<12)&0xf800f800) | ((b<<6)&0x7e007e0) | (c&0x1f001f); if (cell[lw+1]&0x80000000) w |= 0x20; if (cell[lw-LW32+1]&0x80000000) w |= 0x800; bit |= ((rule4[w>>16]<<16) | rule4[w&0xffff]); cxor[lw]=bit;} cnt=0; for (lw=LW32; lw>6)&0x7e007e0) | ((c>>12)&0x1f001f); if (cell[lw-1]&1) w |= 0x4000000; if (cell[lw+LW32-1]&1) w |= 0x100000; bit = ((rule4[w>>16]<<16) | rule4[w&0xffff])<<12; w = ((a<<4)&0xf800f800) | ((b>>2)&0x7e007e0) | ((c>>8)&0x1f001f); bit |= ((rule4[w>>16]<<16) | rule4[w&0xffff])<<8; w = ((a<<8)&0xf800f800) | ((b<<2)&0x7e007e0) | ((c>>4)&0x1f001f); bit |= ((rule4[w>>16]<<16) | rule4[w&0xffff])<<4; w = ((a<<12)&0xf800f800) | ((b<<6)&0x7e007e0) | (c&0x1f001f); if (cell[lw+1]&0x80000000) w |= 0x20; if (cell[lw-LW32+1]&0x80000000) w |= 0x800; bit |= ((rule4[w>>16]<<16) | rule4[w&0xffff]); cxor[lw]=bit;} cnt=0; for (lw=LW32; lw>5)] |= 1<<(31-(jm&31));} }; } fclose(readpattern); LinkCells(); } BarfPattern() {int i, j; for (i=LH/3; i>5)] ^= (RAND<0.5?1:0)<<(31-(j&31));} LinkCells(); } ClearPattern() {int l; for (l=0; l0 && !Button()) {tc1=TickCount(); ct=Toroid?(Perverse!=RawMode?CellTickRawToroid():CellTickToroid()): (Perverse!=RawMode?CellTickRaw():CellTick()); tc2=TickCount(); nt--; if (!(nt%dint)) { sprintf(ln,"%9d %34d words %9d ticks-%c", nt,ct,tc2-tc1,Perverse!=RawMode?'R':'L'); Annotate(ln); CopyBits(&BM1, &graphicWindow->portBits, &BMR, &WMR, 0, 0); } if (!RawMode && ct>(LRratio*LS32)/100) RawMode=1; else if (RawMode && ct<(LRratio*LS32)/110) {RawMode=0; LinkCells();}; } if(RawMode) LinkCells(); }; main() {int nt, lp, c; static dint=1; static char *Help = "T torus, B bound, R read, C clear, U unchuck\n() rule, tick, ? help, Q quit, d display interval\n"; CreateArrays(); BMB.top=0; BMB.left=0; BMB.bottom=LH; BMB.right=LW; /* cell array bounds */ BM1.baseAddr = (char *) cell; BM1.rowBytes = LW32<<2; BM1.bounds = BMB; BMR.left=0; BMR.right=LW; BMR.top=1; BMR.bottom=LH-1; /* cell source region */ open_graphic_window(MaxX=LW+16,MaxY=LH+32,"HexLife"); WMR.left=8+BMR.left; WMR.right=8+BMR.right; /* screen destination region */ WMR.top=8+BMR.top; WMR.bottom=8+BMR.bottom; Donut(); MakeRule(RULE); /* Make transition table from rule */ PrintRule(); Annotate(RULE); ReadPattern(); CopyBits(&BM1, &graphicWindow->portBits, &BMR, &WMR, 0, 0); printf(Help); ln[lp=0]=0; nt=0; while (1) {while (!(c=ln[lp++])) {gets(ln); lp=0;} if(c=='Q' || c=='q') {printf("bye!\n"); exit(0);} else if(c=='?') printf(Help); else if(c=='D' || c=='d') sscanf(&(ln[1]),"%d",&dint); else if(c=='T' || c=='t') {printf("Toroidal array\n"); Donut(); LinkCells();} else if(c=='B' || c=='b') {printf("Bounded array\n"); DeadEnd(); LinkCells();} else if(c=='(') {if (!MakeRule(ln)) printf("Error in rule\n"); PrintRule(); LinkCells(); Annotate(ln);} else if(c=='r' || c=='R') {ReadPattern(); CopyBits(&BM1, &graphicWindow->portBits, &BMR, &WMR, 0, 0);} else if(c=='u' || c=='U') {BarfPattern(); CopyBits(&BM1, &graphicWindow->portBits, &BMR, &WMR, 0, 0);} else if(c=='c' || c=='C') {ClearPattern(); CopyBits(&BM1, &graphicWindow->portBits, &BMR, &WMR, 0, 0);} else if (c>='0' && c<='9') {sscanf(&ln[lp-1],"%d",&nt); DoTicks(nt,dint); ln[lp]=0; nt=0;} } }