more work done
This commit is contained in:
		
							parent
							
								
									9675b16dfe
								
							
						
					
					
						commit
						827b747bd3
					
				@ -3,13 +3,15 @@ program noisepic
 | 
			
		||||
  use spitpgm
 | 
			
		||||
  use pixrgb
 | 
			
		||||
  use noisepictures
 | 
			
		||||
  use mathstuff2
 | 
			
		||||
  implicit none
 | 
			
		||||
 | 
			
		||||
  integer                   :: numframe = 0
 | 
			
		||||
 | 
			
		||||
  integer                   :: nbarg, nbre
 | 
			
		||||
  integer                   :: nbarg
 | 
			
		||||
  character(len=256)        :: arg
 | 
			
		||||
  integer                   :: ranges(6)
 | 
			
		||||
  real                      :: fclock, kpi, r1, r3, r5
 | 
			
		||||
 | 
			
		||||
  nbarg = IARGC()
 | 
			
		||||
  if (nbarg .GT. 0) then
 | 
			
		||||
@ -18,134 +20,48 @@ program noisepic
 | 
			
		||||
       read (arg, *) numframe
 | 
			
		||||
  endif
 | 
			
		||||
 | 
			
		||||
  ranges(1) = 10    ;    ranges(2) = 90
 | 
			
		||||
  ranges(3) = 110   ;    ranges(4) = 166
 | 
			
		||||
  ranges(5) = 205   ;    ranges(6) = 230
 | 
			
		||||
  nbre = 1000+(numframe*555)
 | 
			
		||||
  call make_noise_bw_pic (numframe)
 | 
			
		||||
  call init_random_seed()
 | 
			
		||||
 | 
			
		||||
  kpi = 3.151592654 / 3.0
 | 
			
		||||
 | 
			
		||||
  do numframe = 0, 479
 | 
			
		||||
    fclock = kpi * float(numframe) / 480.0
 | 
			
		||||
    r1 = 27000 + 20000 * cos(fclock*26)
 | 
			
		||||
    ranges(1) = nint(r1)    ; ranges(2) = ranges(1)+300
 | 
			
		||||
 | 
			
		||||
    r3 = 32000 + 28000 * cos(fclock*29)
 | 
			
		||||
    ranges(3) = nint(r3)    ; ranges(4) = ranges(3)+300
 | 
			
		||||
 | 
			
		||||
    r5 = 29000 + 23000 * cos(fclock*32)
 | 
			
		||||
    ranges(5) = nint(r5)    ; ranges(6) = ranges(5)+300
 | 
			
		||||
 | 
			
		||||
    print *, 'r123', numframe, fclock, r1, r3, r5
 | 
			
		||||
 | 
			
		||||
    call make_noise_color_range_pic (numframe, ranges, 29000)
 | 
			
		||||
  enddo
 | 
			
		||||
 | 
			
		||||
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)
 | 
			
		||||
  call noise_gray8_pic(pic, 15000)
 | 
			
		||||
 | 
			
		||||
  write (filename, "(a, i5.5, a)") "", value, ".pgm"
 | 
			
		||||
  call spit_as_pgm_8(pic, trim(filename))
 | 
			
		||||
end subroutine
 | 
			
		||||
!--
 | 
			
		||||
!-- ------------------------------------------------------------------
 | 
			
		||||
!-- ------------------------------------------------------------------
 | 
			
		||||
!-
 | 
			
		||||
!-	Colorized
 | 
			
		||||
!-
 | 
			
		||||
subroutine make_noise_color_pic (value)
 | 
			
		||||
subroutine make_noise_color_range_pic (seqv, rngs, nbre)
 | 
			
		||||
  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)        :: seqv, nbre
 | 
			
		||||
  integer, intent(in)        :: rngs(6)
 | 
			
		||||
 | 
			
		||||
  integer                          :: foo
 | 
			
		||||
  type(t_pixrgb), allocatable      :: pix(:,:)
 | 
			
		||||
  character (len=280)              :: filename
 | 
			
		||||
 | 
			
		||||
  allocate(pix(320, 240))
 | 
			
		||||
  allocate(pix(640, 480))
 | 
			
		||||
  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/", seqv, ".pnm"
 | 
			
		||||
  ! print *, 'filename: ', trim(filename)
 | 
			
		||||
 | 
			
		||||
  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))
 | 
			
		||||
  call noise_range_rgb16_pic(pix, rngs, nbre)
 | 
			
		||||
  call rgbpix_spit_as_pnm_16(pix, trim(filename))
 | 
			
		||||
 | 
			
		||||
  deallocate(pix)
 | 
			
		||||
 | 
			
		||||
end subroutine
 | 
			
		||||
 | 
			
		||||
!-- ------------------------------------------------------------------
 | 
			
		||||
end program
 | 
			
		||||
 | 
			
		||||
		Loading…
	
		Reference in New Issue
	
	Block a user