Fortraneries/Modules/chkpixels.f90

70 lines
1.6 KiB
Fortran
Raw Normal View History

!-------------------------------------------------------------------
!-
2022-12-01 12:03:22 +01:00
program chkpixels
2022-12-16 19:26:54 +01:00
use spitpgm
use pixrgb
use trials ! experiments, ymmv.
2022-12-01 12:03:22 +01:00
implicit none
2022-12-01 12:03:22 +01:00
write(0, *) "------ CHKPIXELS ------"
2023-01-07 10:40:29 +01:00
call test_spit_as(3)
call test_spit_rgb(128, 222)
2022-12-01 12:03:22 +01:00
STOP 'BECAUSE NO CPU AVAILABLE'
contains
!-------------------------------------------------------------------
2022-12-24 22:13:17 +01:00
!-
! exerciser for the 'pixrgb' module
2022-12-01 12:03:22 +01:00
!-
2023-01-07 10:40:29 +01:00
subroutine test_spit_rgb(sz, kg)
integer, intent(in) :: sz, kg
2022-12-16 19:26:54 +01:00
type(t_pixrgb), allocatable :: pixrgb(:,:)
integer :: ix, iy
print *, "test spit rgb", sz
allocate(pixrgb(sz, sz))
2022-12-24 22:13:17 +01:00
call rgbpix_set_to_zero(pixrgb)
2022-12-16 19:26:54 +01:00
do ix=1, sz
do iy=1, sz
pixrgb(ix, iy)%r = ix
2023-01-07 10:40:29 +01:00
pixrgb(ix, iy)%g = mod(ix*iy, kg)
2022-12-16 19:26:54 +01:00
pixrgb(ix, iy)%b = iy
end do
end do
2022-12-17 12:09:57 +01:00
call rgbpix_spit_as_pnm_8(pixrgb, "rgb.pnm")
2022-12-16 19:26:54 +01:00
deallocate(pixrgb)
end subroutine
!-------------------------------------------------------------------
!-
subroutine test_spit_as(increment)
integer, intent(in) :: increment
2022-12-01 12:03:22 +01:00
integer, parameter :: SZ = 40
2022-12-01 12:03:22 +01:00
integer, dimension(SZ, SZ) :: greymap
integer :: ix, iy, value
2023-01-07 10:40:29 +01:00
print *, "test spit as", sz
2022-12-01 12:03:22 +01:00
value = 0
do iy=1, SZ
do ix=1, SZ
greymap(ix, iy) = value
value = value + increment
2022-12-01 12:03:22 +01:00
enddo
enddo
2023-01-07 10:40:29 +01:00
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')
2022-12-01 12:03:22 +01:00
end subroutine
end program
!-------------------------------------------------------------------