!------------------------------------------------------------------- !- program chkpixels use spitpgm use pixrgb use trials ! experiments, ymmv. implicit none write(0, *) "------ CHKPIXELS ------" call test_spit_as(3) call test_spit_rgb(128, 222) STOP 'BECAUSE NO CPU AVAILABLE' contains !------------------------------------------------------------------- !- ! exerciser for the 'pixrgb' module !- subroutine test_spit_rgb(sz, kg) integer, intent(in) :: sz, kg type(t_pixrgb), allocatable :: pixrgb(:,:) integer :: ix, iy print *, "test spit rgb", sz allocate(pixrgb(sz, sz)) call rgbpix_set_to_zero(pixrgb) do ix=1, sz do iy=1, sz pixrgb(ix, iy)%r = ix pixrgb(ix, iy)%g = mod(ix*iy, kg) pixrgb(ix, iy)%b = iy end do end do call rgbpix_spit_as_pnm_8(pixrgb, "rgb8.pnm") call rgbpix_spit_as_pnm_16(pixrgb, "rgb16.pnm") deallocate(pixrgb) end subroutine !------------------------------------------------------------------- !- subroutine test_spit_as(increment) integer, intent(in) :: increment integer, parameter :: SZ = 40 integer, dimension(SZ, SZ) :: greymap integer :: ix, iy, value print *, "test spit as", sz value = 0 do iy=1, SZ do ix=1, SZ greymap(ix, iy) = value value = value + increment enddo enddo ! call spit_as_pgm_16 (greymap, 'a.pnm') ! call spit_as_pgm_eq (greymap, 'b.pnm') call spit_as_pgm_8 (greymap, 'c.pnm') call new_spit_a (greymap, 'x.pnm') end subroutine end program !-------------------------------------------------------------------