Fortraneries/GrafAnim/essai.f90

100 lines
2.5 KiB
Fortran
Raw Normal View History

2022-10-28 22:18:39 +02:00
program essai
2023-10-10 22:08:50 +02:00
2024-02-07 03:22:44 +01:00
! *******************************************
! CE TRUC NE MARCHE PAS /O\
! *******************************************
2023-10-10 22:08:50 +02:00
use pixrgb
2022-10-28 22:18:39 +02:00
implicit none
2022-11-13 23:47:45 +01:00
integer :: nbarg
2023-10-10 22:08:50 +02:00
integer :: param0 = 10
2022-11-26 13:01:37 +01:00
character(len=256) :: arg
2022-11-13 23:47:45 +01:00
2023-10-10 22:08:50 +02:00
! integer :: foo, bar
integer :: width = 512
integer :: height = 342
integer :: seqnum
real :: nclock, kx, ky
character (len=280) :: filename
type(t_pixrgb), allocatable :: pix(:,:)
write(0, *) "--------- essai FLUFFYWAVES ------------"
2022-11-13 23:47:45 +01:00
nbarg = IARGC()
if (nbarg .GT. 0) then
call GETARG(1, arg)
2022-11-22 08:58:56 +01:00
! write (0, '(A40, A5)') "argument = ", arg
2023-10-10 22:08:50 +02:00
read (arg, *) param0
2022-11-13 23:47:45 +01:00
endif
2023-10-10 22:08:50 +02:00
allocate(pix(width, height))
2022-11-13 23:47:45 +01:00
2023-10-10 22:08:50 +02:00
do seqnum = 0, param0
nclock = float(seqnum) / float(param0)
call rgbpix_set_to_rgb(pix, 0, 0, 0)
2022-11-13 23:47:45 +01:00
2023-10-10 22:08:50 +02:00
kx = nclock * 0.35 * sin(nclock * 7.0)
ky = nclock * 0.95 * cos(nclock * 7.0)
call iterator (pix, kx, ky, 50000)
2022-11-22 08:58:56 +01:00
2023-10-10 22:08:50 +02:00
write (filename, "(a, i5.5, a)") "./F/np/", seqnum, ".pnm"
write(0, *) seqnum, kx, ky, trim(filename)
call rgbpix_spit_as_pnm_16(pix, trim(filename))
2022-11-13 23:47:45 +01:00
enddo
2023-10-10 22:08:50 +02:00
contains
! ----------------------------------------------------------
!-
subroutine setpixel(pic, x, y)
implicit none
type(t_pixrgb), intent(inout) :: pic(:,:)
real, intent(in) :: x, y
integer :: ix, iy
ix = 600 - int (300.0 * x)
iy = 600 - int (300.0 * y)
2022-11-22 08:58:56 +01:00
2023-10-10 22:08:50 +02:00
! print *, ix, iy
2022-11-13 23:47:45 +01:00
2023-10-10 22:08:50 +02:00
if ( (ix .gt. lbound(pic, 1)) .and. (ix .lt. ubound(pic, 1)) &
.and. &
(iy .gt. lbound(pic, 2)) .and. (iy .lt. ubound(pic, 2)) ) &
then
2024-02-07 03:22:44 +01:00
pix(ix, iy)%r = 0
2023-10-10 22:08:50 +02:00
pic(ix, iy)%g = 65000
pic(ix, iy)%b = 20000
else
! XXX write(0, *) 'out', ix, iy
endif
end subroutine
2022-10-28 22:18:39 +02:00
2023-10-10 22:08:50 +02:00
! ----------------------------------------------------------
!-
subroutine iterator(img, x0, y0, nbi)
implicit none
type(t_pixrgb), intent(inout) :: img(:,:)
real, intent(in) :: x0, y0
integer, intent(in) :: nbi
real :: xa, ya, xb, yb
integer :: bcl
xa = x0 ; ya = y0
do bcl=0, nbi
xb = xa - 0.4 * sin ( ya + sin( 0.4 * ya ) )
yb = ya - 0.4 * sin ( xa + sin( -2 * xa ) )
call setpixel(img, xb, yb)
xa = xb
ya = yb
enddo
2022-10-28 22:18:39 +02:00
2022-11-13 23:47:45 +01:00
end subroutine
2022-10-28 22:18:39 +02:00
end program