program noisepic use spitpgm use pixrgb implicit none integer :: numframe = 0 integer :: nbarg, nbre character(len=256) :: arg integer :: ranges(6) nbarg = IARGC() if (nbarg .GT. 0) then call GETARG(1, arg) ! write (0, '(A40, A5)') "argument = ", arg read (arg, *) numframe endif ranges(0) = 10 ; ranges(2) = 90 ranges(3) = 110 ; ranges(4) = 166 ranges(5) = 205 ; ranges(6) = 230 nbre = 1000+(numframe*555) call make_noise_color_range_pic(numframe, ranges, nbre) contains !-- ------------------------------------------------------------------ !- !- Black & White !- subroutine make_noise_bw_pic (value) implicit none integer, intent(in) :: value integer :: foo integer, dimension(:,:), allocatable :: pic character (len=280) :: filename allocate(pic(320, 240)) pic = 30 !- clear the picz call srand(value+34) foo = irand() print *, 'val=', value, ' rnd=', foo call plot_noise_bw_pic(pic, 15000) write (filename, "(a, i5.5, a)") "", value, ".pgm" call spit_as_pgm_8(pic, trim(filename)) end subroutine !-- ------------------------------------------------------------------ subroutine plot_noise_bw_pic(picz, nbre) implicit none integer, dimension(:,:), intent(inout) :: picz integer, intent(in) :: nbre integer :: width, height integer :: quux, ix, iy, iv width = ubound(picz, 1) ; height = ubound(picz, 2) ! print *, 'sz picz', width, height do quux=1, nbre ix = 1 + mod ( irand(), width ) iy = 1 + mod ( irand(), height ) iv = mod ( irand(), 256 ) ! print *, ix, iy picz(ix, iy) = iv enddo end subroutine !-- ------------------------------------------------------------------ !- !- Colorized !- subroutine make_noise_color_pic (value) implicit none integer, intent(in) :: value integer :: foo type(t_pixrgb), dimension(:,:), allocatable :: pix character (len=280) :: filename allocate(pix(320, 240)) call rgbpix_set_to_rgb(pix, 30, 30, 60) call srand(value+34) foo = irand() print *, 'val=', value, ' rnd=', foo call plot_noise_color_pic(pix, 15000) write (filename, "(a, i5.5, a)") "./", value, ".pnm" call rgbpix_spit_as_pnm_8(pix, trim(filename)) end subroutine !-- ------------------------------------------------------------------ subroutine plot_noise_color_pic(prgb, nbre) implicit none type(t_pixrgb), dimension(:,:), intent(inout) :: prgb integer, intent(in) :: nbre integer :: quux, ix, iy, width, height width = ubound(prgb, 1) ; height = ubound(prgb, 2) do quux=1, nbre ix = 1 + mod ( irand(), width ) iy = 1 + mod ( irand(), height ) prgb(ix, iy)%r = 64 + mod ( irand(), 127 ) prgb(ix, iy)%g = 64 + mod ( irand(), 127 ) prgb(ix, iy)%b = 64 + mod ( irand(), 127 ) enddo end subroutine !-- ------------------------------------------------------------------ !- !- Colorized with range !- subroutine plot_noise_color_range_pic(prgb, nbre) implicit none type(t_pixrgb), dimension(:,:), intent(inout) :: prgb integer, intent(in) :: nbre integer :: quux, ix, iy, width, height width = ubound(prgb, 1) ; height = ubound(prgb, 2) do quux=1, nbre ix = 1 + mod ( irand(), width ) iy = 1 + mod ( irand(), height ) prgb(ix, iy)%r = 64 + mod ( irand(), 127 ) prgb(ix, iy)%g = 64 + mod ( irand(), 127 ) prgb(ix, iy)%b = 64 + mod ( irand(), 127 ) enddo end subroutine !-- ------------------------------------------------------------------ subroutine make_noise_color_range_pic (value, rngs, nbre) implicit none integer, intent(in) :: value, nbre integer, intent(in) :: rngs(6) integer :: foo type(t_pixrgb), allocatable :: pix(:,:) character (len=280) :: filename allocate(pix(320, 240)) call rgbpix_set_to_rgb(pix, 0, 0, 0) call srand(value+34) foo = irand() print *, 'color_range: val=', value, 'rnd=', foo, 'nbre=', nbre write (filename, "(a, i5.5, a)") "./F/np/", value, ".pnm" print *, 'filename: ', trim(filename) call plot_noise_color_range_pic(pix, nbre) call rgbpix_spit_as_pnm_8(pix, trim(filename)) deallocate(pix) end subroutine !-- ------------------------------------------------------------------ end program