Fortraneries/GrafAnim/soundscope.f90

210 lines
5.4 KiB
Fortran

! *****************************************************
!
! *****************************************************
program soundscope
use pixrgb
use utils_ga
implicit none
integer :: width = 720
integer :: height = 576
integer :: marge = 32
integer :: samplerate = 44100
integer :: framerate = 30
type(t_pixrgb), allocatable :: pix(:,:)
character (len=280) :: filename
integer :: iter, foo, tx, ty
integer :: smppf
logical :: flagdone
smppf = samplerate / framerate
allocate(pix(width, height))
call fill_random_gauss(pix, 65000, marge)
iter = 0
do
write(0, *) "----- iteration", iter, " -----"
iter = iter + 1
do foo=0, 100
tx = (marge/2) + fair_random_gauss(width-marge)
ty = (marge/2) + fair_random_gauss(height-marge)
if (is_pixel_inside(tx, ty)) then
call make_red_dot(pix, tx, ty)
endif
tx = (marge/2) + fair_random_gauss(width-marge)
ty = (marge/2) + fair_random_gauss(height-marge)
if (is_pixel_inside(tx, ty)) then
call make_blue_dot(pix, tx, ty)
endif
enddo
call dim_pix_rgb_mul(pix, 0.86)
if (mod(iter, 180) .LT. 90) then
call make_a_frame_dplot(pix, smppf, flagdone)
else
call make_a_frame_xy(pix, smppf, flagdone)
endif
call dessine_cadre(pix, 65000, 65000, 65000, marge)
write (filename, "(a,i5.5,a)") "./F/np/", iter, ".pnm"
call rgbpix_spit_as_pnm_16(pix, filename)
if (flagdone) then
exit
endif
enddo
write(0, *) " [done]"
contains
!-- ------------------------------------------------------------------
!--
subroutine make_a_frame_xy(image, nbdata, jobdone)
type(t_pixrgb), intent(inout) :: image(:,:)
integer, intent(in) :: nbdata
logical, intent(out) :: jobdone
integer :: idx, errcode
real :: vl, vr
integer :: ix, iy
jobdone = .FALSE.
do idx=0, nbdata
! get a sample
read(5, *, iostat=errcode) vl, vr
if (0 .NE. errcode) then
write(0, *) "iostat", errcode
jobdone = .TRUE.
exit
endif
! add flash !
if ( (idx .LT. 100) .AND. &
((abs(vl).GT.21000).OR.(abs(vr).GT.21000)) ) then
write(0,*) "overshoot!"
call fill_random_gauss(image, 65000, marge)
endif
! scale it to the window
ix = width - ((2 * int(vl / 111.111)) + 400)
iy = (2 * int(vr / 166.666)) + 300
if (is_pixel_inside(ix, iy)) then
call make_big_dot(image, ix, iy)
endif
enddo
end subroutine
!-- ------------------------------------------------------------------
!-- ------------------------------------------------------------------
!--
subroutine make_a_frame_dplot(image, nbdata, jobdone)
type(t_pixrgb), intent(inout) :: image(:,:)
integer, intent(in) :: nbdata
logical, intent(out) :: jobdone
integer :: idx, errcode
real :: vl, vr
integer :: il, ir, xpos
jobdone = .FALSE.
xpos = 1
do idx=0, nbdata
! get a sample
read(5, *, iostat=errcode) vl, vr
if (0 .NE. errcode) then
write(0, *) "iostat", errcode
jobdone = .TRUE.
exit
endif
! add flash !
if ( (idx .LT. 100) .AND. &
((abs(vl).GT.21000).OR.(abs(vr).GT.21000)) ) then
write(0,*) "overshoot!"
call fill_random_gauss(image, 65000, marge)
endif
if (xpos .LT. width) then
! scale it to the window
il = int((vl/65536.9) * real(height)) + height/2
ir = int((vr/65536.9) * real(height)) + height/2
! print *, vl, il, " | ", vr, ir
if (is_pixel_inside(xpos, il)) then
call make_big_dot(image, xpos, il)
endif
if (is_pixel_inside(xpos, ir)) then
call make_big_dot(image, xpos, ir)
endif
xpos = xpos + 1
endif
enddo
end subroutine
!-- ------------------------------------------------------------------
subroutine dessine_cadre(image, R, G, B, border)
type(t_pixrgb), intent(inout) :: image(:,:)
integer,intent(in) :: R, G, B, border
integer :: ix, iy, foo
foo = ubound(image, 2) - border
do ix=1+marge, ubound(image, 1) - border
image(ix, marge)%r = R
image(ix, marge)%g = G
image(ix, marge)%b = B
image(ix, foo)%r = R
image(ix, foo)%g = G
image(ix, foo)%b = B
enddo
foo = ubound(image, 1) - border
do iy=1+marge, ubound(image, 2)-border
image(marge, iy)%r = R
image(marge, iy)%g = G
image(marge, iy)%b = B
image(foo, iy)%r = R
image(foo, iy)%g = G
image(foo, iy)%b = B
enddo
end subroutine
!-- ------------------------------------------------------------------
function is_pixel_inside(ix, iy)
integer,intent(in) :: ix, iy
logical :: is_pixel_inside
is_pixel_inside = .TRUE.
if ( (ix .LT. marge) .OR. (ix .GT. width-marge) ) then
is_pixel_inside = .FALSE.
return
endif
if ( (iy .LT. marge) .OR. (iy .GT. height-marge) ) then
is_pixel_inside = .FALSE.
return
endif
end function
!-- ------------------------------------------------------------------
!-- ------------------------------------------------------------------
end program soundscope