Donut math in Fortran

I thought I’d have a go at converting Andy Sloane’s lovely little spinning donut obfuscated C code to Fortran. You can find the original C code and detailed explanation here.

Here is my Fortran equivalent:

                       program donut
               implicit none;integer c1,c2,&
           cr,x,y,o,nn,k;real aa,bb,dd,c,d,e,f,g,&
       h,i,j,l,m,n,t,z(0:1759); character, parameter &
      :: s(0:11)=[".",",","-","~",":",";","=","!","*",&
     "#","$","@"]; character b(0:1759);aa=0.0;bb=0.0; do
    write(*,*) char(27)//'[H'//char(27)//'[J'; b(:)=" ";z&
   (:)=0.0;j=0.0;do while(j<     6.28);i=0.0; do while(i <&
   6.28);c=sin(i); d=cos             (j);e=sin(aa);f=sin(j)
  g=cos(aa); h=d+2.0;dd                =1.0/(c*h*e+f*g+5.0)
  l=cos(i);m=cos(bb);n                 =sin(bb); t=c*h*g-f*e
  x=40+30*dd*(l*h*m-t*n                );y=12+15*dd*(l*h*n+t&
  *m);o=x+80*y;nn=abs(8                *((f*e-c*d*g)*m-c*d*e&
  -f*g-l*d*n));if((22>y)             .and.(y>0).and.(x > 0)&
  .and.(80 > x).and.(dd > z        (o))) then;z(o)=dd;if(nn&
   > 0) then;b(o)=s(nn);else;b(o)=s(0);end if;end if;i=i+&
    0.02;end do;j=j+0.07;end do;do k=0,1759,80;write(*,&
     '(80A)') b(k:k+79);end do;aa=aa+0.04; bb=bb+0.02
       call system_clock(count=c1,count_rate=cr);c2&
         =c1+int(0.05*cr);do while (c1 < c2);call&
               system_clock(count=c1);end do
                    end do;end program

It should work on all Linux machines in a regular terminal. I’m not sure about Windows though.

I’ve tested it on GFortran, Classic Intel Fortran, the new IFX Fortran, NAG Fortran and NVIDIA Fortran and all work. LFortran is not working yet but I’ll submit a bug report to the developers.

The conversion was mostly quite easy. I had to put in a delay to stop it spinning too fast: it would be nice if Fortran had a millisecond delay as part of the standard. Even taking this into account, the original C code is quite a bit more compact.

Here is the un-obfuscated code:

program donut
implicit none
integer c1,c2,cr,x,y,o,nn,k
real aa,bb,dd,c,d,e,f,g,h,i,j,l,m,n,t,z(0:1759)
character, parameter :: s(0:11)=[".",",","-","~",":",";","=","!","*","#","$","@"]
character b(0:1759)
aa=0.0
bb=0.0
do
  write(*,*) char(27)//'[H'//char(27)//'[J'
  b(:)=" "
  z(:)=0.0
  j=0.0
  do while(j < 6.28)
    i=0.0
    do while(i < 6.28)
      c=sin(i)
      d=cos(j)
      e=sin(aa)
      f=sin(j)
      g=cos(aa)
      h=d+2.0
      dd=1.0/(c*h*e+f*g+5.0)
      l=cos(i)
      m=cos(bb)
      n=sin(bb)
      t=c*h*g-f*e
      x=40+30*dd*(l*h*m-t*n)
      y=12+15*dd*(l*h*n+t*m)
      o=x+80*y
      nn=abs(8*((f*e-c*d*g)*m-c*d*e-f*g-l*d*n))
      if ((22 > y).and.(y > 0).and.(x > 0).and.(80 > x).and.(dd > z(o))) then
        z(o)=dd
        if (nn > 0) then
          b(o)=s(nn)
        else
          b(o)=s(0)
        end if
      end if
      i=i+0.02
    end do
    j=j+0.07
  end do
  do k=0,1759,80
    write(*,'(80A)') b(k:k+79)
  end do
  aa=aa+0.04
  bb=bb+0.02
  call system_clock(count=c1,count_rate=cr)
  c2=c1+int(0.05*cr)
  do while (c1 < c2)
    call system_clock(count=c1)
  end do
end do
end program

See if you can make it even more compact…
JK.

8 Likes

A related previous thread:

1 Like

Thanks for pointing that out – I probably should have searched for it first!

Anyway, it was fun converting the code and it uncovered an LFortran bug in the process.

After fixed form and free form, this is the donut form!

2 Likes

I guess this is what is meant by taking a “hole-listic” approach to programming. On my monitor it even looks like its covered with purple, green and gold “sprinkles”. That had to take a lot of thought :smile:

2 Likes

Pronounced as “do-not form”.

It deserves a new Fortran file extension: .dnf
Let’s reclaim that extension!