I have always been taught that blue is the color of lies because you
have fewer cones sensitive to blue so that you don't get as clear a
picture in blue as in red or green.
I have always been taught that blue is the color of lies because you
have fewer cones sensitive to blue so that you don't get as clear a
picture in blue as in red or green.
On Wednesday, August 31, 2022 at 12:07:49 AM UTC-7, James Van Buskirk wrote:
I have always been taught that blue is the color of lies because youOK, here it is in Fortran. The original was before C had complex,
have fewer cones sensitive to blue so that you don't get as clear a
picture in blue as in red or green.
and it looks much nicer with complex variables.
(Note that it is fixed form, and many news readers lose leading blanks.)
PROGRAM ROOT3
REAL*8 PI/3.141592653589793/, CONST/1.905E-3/, R2R/.4/
INTEGER ROWS/900/, COLS/900/, R/150/
REAL*8 ANGLE
COMPLEX*16 Z, W, D
INTEGER I, J, GRAY, IX, IY
CHARACTER*50 PS(7)
DATA PS/"%!",
* "/str 256 string def",
* "/go { image showpage } def",
* "0 720 translate 72 72 scale",
* "(I6, I6, ' 8 [', I6, ' 0 0 ', I6, ' 0 ', I6, ']')",
* "{currentfile str readhexstring pop}",
* "go"/
DO I=1,4
WRITE(*,'(A)') PS(I)
END DO
WRITE(*,PS(5)) ROWS, COLS, R, -R, R
DO I=6,7
WRITE(*,'(A)') PS(I)
END DO
DO IX=-ROWS/2, ROWS-ROWS/2-1
DO IY=-COLS/2, COLS-COLS/2-1
Z=CMPLX(IX*CONST, IY*CONST, KIND(1.D0))
DO I=1,224
W=Z*Z
Z=Z*W*2+1
Z=Z/W/3
D=Z-1
IF(ABS(D)<R2R) EXIT
D=Z+CMPLX(0.5D0, 0.866D0, KIND(1.D0))
IF(ABS(D)<R2R) EXIT
D=Z+CMPLX(0.5D0, -0.866D0, KIND(1.D0))
IF(ABS(D)<R2R) EXIT
END DO
IF(I>224) THEN
ANGLE=ATAN2(0.,1.)
ELSE
ANGLE=ATAN2(AIMAG(D), REAL(D))
ENDIF
WRITE(*,'(Z2)') INT(ABS(ANGLE/0.012272))
END DO
END DO
END
The beauty that can emerge from math can be startling. Nice image.
It was fun playing with the formula and seeing the different results.
Just a note that to work in my programming environment I had to change
the Z2 format to Z2.2.
On Wednesday, August 31, 2022 at 12:07:49 AM UTC-7, James Van Buskirk wrote:
I have always been taught that blue is the color of lies because youOK, here it is in Fortran. The original was before C had complex,
have fewer cones sensitive to blue so that you don't get as clear a picture in blue as in red or green.
and it looks much nicer with complex variables.
(Note that it is fixed form, and many news readers lose leading blanks.)
REAL*8 PI/3.141592653589793/, CONST/1.905E-3/, R2R/.4/Why is it that experienced programmers still get this wrong
after 50 years? All those constants need D0, D-3, D0 respectively.
I tried to view the result of this Fortran program with ghostscript and got rubbish.
I also tried the result of the C program and that showed the picture I expected.
So there is something different, possibly caused by the formatting.
But I am no expert in PostScript.
On Wednesday, August 31, 2022 at 11:49:35 PM UTC-7, Robin Vowels wrote:.
(snip)
They really don't, and even more probably don't need to be REAL*8.REAL*8 PI/3.141592653589793/, CONST/1.905E-3/, R2R/.4/Why is it that experienced programmers still get this wrong
after 50 years? All those constants need D0, D-3, D0 respectively.
Especially as PI isn't even used in the program!
In the end, the program converts an angle to a gray level from 0 to 255, which the printer likely converts to a coarser gray level.
CONST relates to the scale of the image, which also doesn't need
to be very exact.
On Thursday, September 1, 2022 at 1:39:32 AM UTC-7, arjen.m...@gmail.com wrote:
(snip)
I tried to view the result of this Fortran program with ghostscript and got rubbish.
I also tried the result of the C program and that showed the picture I expected.
So there is something different, possibly caused by the formatting.
But I am no expert in PostScript.
Yes, as John noted the format should be Z2.2.
It is not so obvious, but PS reads the hex characters ignoring any other characters.
With Z2 it blank pads, so only one digit. Z2.2 zero pads, so it works.
The C program uses %02x, which also zero pads.
On 9/1/2022 3:57 AM, gah4 wrote:
Yes, as John noted the format should be Z2.2.
It is not so obvious, but PS reads the hex characters ignoring any other characters.
With Z2 it blank pads, so only one digit. Z2.2 zero pads, so it works.
The C program uses %02x, which also zero pads.
Another tiny correction to the program:
When ix = iy = 0, the statement
Z=Z/W/3
causes division of complex zero by complex zero to occur. With some
Fortran compilers, this might result in '**' to be printed out
instead of two hex digits; in that case, a Postscript interpreter
may abort the display of the image file.
program root3
integer,parameter :: dp=kind(0.0d0)
real(kind=dp),parameter :: const=1.905e-3_dp, r2r=0.4e0_dp
integer,parameter :: rows=900, cols=900, r=150
real(kind=dp) :: angle
complex(kind=dp) :: z, w, d
integer :: i, ix, iy, linebreak
character(len=2) :: zup
character(len=60) :: ps(7)=[character(len=60) :: &
&"%!", &
& "/str 256 string def", &
& "/go { image showpage } def", &
& "0 720 translate 72 72 scale", &
& "(I0, 1x, I0, ' 8 [', I0, ' 0 0 ', I0, ' 0 ', I0, ']')", &
& "{currentfile str readhexstring pop}", &
& "go" ]
write(*,'(A)') (trim(ps(i)),i=1,4)
write(*,ps(5)) rows, cols, r, -r, r
write(*,'(A)')(trim(ps(i)),i=6,7)
linebreak=0
do ix=-rows/2, rows-rows/2-1
do iy=-cols/2, cols-cols/2-1
z=cmplx(ix*const, iy*const, kind=dp)
do i=1,224
w=z*z
z=z*w*2+1
z=z/w/3
d=z-1
if(abs(d)<r2r) exit
d=z+cmplx(0.5_dp, 0.866_dp, kind=dp)
if(abs(d)<r2r) exit
d=z+cmplx(0.5_dp, -0.866_dp, kind=dp)
if(abs(d)<r2r) exit
enddo
if(i>224) then
angle=atan2(0.0_dp,1.0_dp)
else
angle=atan2(aimag(d), real(d,kind=dp))
endif
write(zup,'(Z2.2)') int(abs(angle/0.012272_dp))
write(*,'(A2)',advance='no') lower(zup)
linebreak=linebreak+1
if(linebreak==30)then
linebreak=0
write(*,*)
endif
enddo
enddo
contains
elemental pure function lower(str) result (string)
! ident="@(#) M_strings lower(3f) Changes a string to lowercase
character(*), intent(in) :: str
character(len(str)) :: string
integer :: i
integer,parameter :: diff = iachar('A')-iachar('a')
string = str
! step thru each letter in the string in specified range
do concurrent (i = 1:len_trim(str))
select case (string(i:i))
case ('A':'Z')
string(i:i) = char(iachar(str(i:i))-diff) ! change letter to miniscule
case default
end select
enddo
end function lower
end program root3
Since it came up, hopefully this demonstrates posting in a newsgroup
with indenting ...
On a Linux box with fpm, ps2pdf, and evince I ran it with
fpm run|ps2pdf - >view.pdf;evince view.pdf
If indented four or more characters that line should show as-is, but a ">" is more reliable for verbatim text.
This is the same program essentially verbatim (hopefully) with the advance='no' added and the Z values lowercased as I was doing a diff on
the output with the C version. So it was tweeked to write thirty values
per line in lowercase to make that easier, and uses the Z2.2 format,
and shows that (hopefully) newgroup viewers leave lines starting with ">" as-is, which should retain indenting. Everything else is just cosmetic to satisfy my personal preferences. It does not address the Z/W/3 issue. Like the original post (with the Z2.2 format) it worked with gfortran, ifort,
and nvfortran.
program root3
integer,parameter :: dp=kind(0.0d0)
real(kind=dp),parameter :: const=1.905e-3_dp, r2r=0.4e0_dp integer,parameter :: rows=900, cols=900, r=150
real(kind=dp) :: angle
complex(kind=dp) :: z, w, d
integer :: i, ix, iy, linebreak
character(len=2) :: zup
character(len=60) :: ps(7)=[character(len=60) :: &
&"%!", &
& "/str 256 string def", &
& "/go { image showpage } def", &
& "0 720 translate 72 72 scale", &
& "(I0, 1x, I0, ' 8 [', I0, ' 0 0 ', I0, ' 0 ', I0, ']')", &
& "{currentfile str readhexstring pop}", &
& "go" ]
write(*,'(A)') (trim(ps(i)),i=1,4)
write(*,ps(5)) rows, cols, r, -r, r
write(*,'(A)')(trim(ps(i)),i=6,7)
linebreak=0
do ix=-rows/2, rows-rows/2-1
do iy=-cols/2, cols-cols/2-1
z=cmplx(ix*const, iy*const, kind=dp)
do i=1,224
w=z*z
z=z*w*2+1
z=z/w/3
d=z-1
if(abs(d)<r2r) exit
d=z+cmplx(0.5_dp, 0.866_dp, kind=dp)
if(abs(d)<r2r) exit
d=z+cmplx(0.5_dp, -0.866_dp, kind=dp)
if(abs(d)<r2r) exit
enddo
if(i>224) then
angle=atan2(0.0_dp,1.0_dp)
else
angle=atan2(aimag(d), real(d,kind=dp))
endif
write(zup,'(Z2.2)') int(abs(angle/0.012272_dp)) write(*,'(A2)',advance='no') lower(zup)
linebreak=linebreak+1
if(linebreak==30)then
linebreak=0
write(*,*)
endif
enddo
enddo
contains
elemental pure function lower(str) result (string)
! ident="@(#) M_strings lower(3f) Changes a string to lowercase character(*), intent(in) :: str
character(len(str)) :: string
integer :: i
integer,parameter :: diff = iachar('A')-iachar('a')
string = str
! step thru each letter in the string in specified range
do concurrent (i = 1:len_trim(str))
select case (string(i:i))
case ('A':'Z')
string(i:i) = char(iachar(str(i:i))-diff) ! change letter to miniscule
case default
end select
enddo
end function lower
end program root3
I tried to view the result of this Fortran program with ghostscript and got rubbish. I also tried the result of the C program and that showed the picture I expected. So there is something different, possibly caused by the formatting. But I am no expertin PostScript.
On Thursday, September 1, 2022 at 10:39:32 AM UTC+2, Arjen Markus wrote:expert in PostScript.
I tried to view the result of this Fortran program with ghostscript and got rubbish. I also tried the result of the C program and that showed the picture I expected. So there is something different, possibly caused by the formatting. But I am no
Since I get a completely contorted picture with the Fortran program I am trying to figure out what is going on. The results are identical between Intel Fortran oneAPI and gfortran, but differ greatly when using the C version.
I have tried analysing the differences between the output from the Fortran program and the C program. So far I can find no cause, but:
- The output file from the C program is roughly 54000 bytes larger
- The number of lines is the same (I used a similar modification as John, but by filling a string of 60 characters)
- The lengths of the lines are equal
- The differences occur in the hexadecimal output but curiously enough not in the actual data (I write out the variables)
Very odd. I must be looking at it in a wrong way.
On 9/1/2022 11:24 PM, Arjen Markus wrote:expert in PostScript.
On Thursday, September 1, 2022 at 10:39:32 AM UTC+2, Arjen Markus wrote:
I tried to view the result of this Fortran program with ghostscript and got rubbish. I also tried the result of the C program and that showed the picture I expected. So there is something different, possibly caused by the formatting. But I am no
Since I get a completely contorted picture with the Fortran program I am trying to figure out what is going on. The results are identical between Intel Fortran oneAPI and gfortran, but differ greatly when using the C version.
I have tried analysing the differences between the output from the Fortran program and the C program. So far I can find no cause, but:
- The output file from the C program is roughly 54000 bytes larger
- The number of lines is the same (I used a similar modification as John, but by filling a string of 60 characters)
- The lengths of the lines are equal
- The differences occur in the hexadecimal output but curiously enough not in the actual data (I write out the variables)
Very odd. I must be looking at it in a wrong way.
Can you post both the Fortran program and the C program?
Louis
Well, that worked for a long time, but google groups at least still shows no indenting. Oops. That thing goes out of it's way to mess up any kind of formatting, etc.
Test for pos < 59 instead of 60 because incrementing by two and I think the Fortran code would work. The example is divisible by 30 so the output line always gets filled, but if the size were changed to something not divisible by 30 the output would befull of the previous pass and not get written; but is OK as it is with the current size.
Sysop: | Keyop |
---|---|
Location: | Huddersfield, West Yorkshire, UK |
Users: | 159 |
Nodes: | 16 (0 / 16) |
Uptime: | 99:45:39 |
Calls: | 3,209 |
Files: | 10,563 |
Messages: | 3,009,979 |