program noisepic use spitpgm implicit none integer :: numframe = 0 integer :: nbarg character(len=256) :: arg nbarg = IARGC() if (nbarg .GT. 0) then call GETARG(1, arg) ! write (0, '(A40, A5)') "argument = ", arg read (arg, *) numframe endif call make_noise_pic(numframe) contains !-- ------------------------------------------------------------------ subroutine make_noise_pic (value) integer, intent(in) :: value integer :: foo integer, dimension(:,:), allocatable :: pic character (len=280) :: filename allocate(pic(320, 240)) pic = 0 call srand(value+34) foo = irand() print *, 'val=', value, ' rnd=', foo call plot_noise_pic(pic, 15000) write (filename, "(a, i5.5, a)") "", value, ".pgm" call spit_as_pgm_8(pic, trim(filename)) end subroutine !-- ------------------------------------------------------------------ subroutine plot_noise_pic(picz, nbre) 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 !-- ------------------------------------------------------------------ end program