Fortraneries/Modules/chkpixels.f90

74 lines
1.5 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 ------"
2022-12-16 19:26:54 +01:00
! call test_spit_as(3)
call test_spit_rgb(256)
2022-12-01 12:03:22 +01:00
STOP 'BECAUSE NO CPU AVAILABLE'
contains
!-------------------------------------------------------------------
!-
2022-12-16 19:26:54 +01:00
subroutine test_spit_rgb(sz)
integer, intent(in) :: sz
type(t_pixrgb), allocatable :: pixrgb(:,:)
integer :: ix, iy
print *, "test spit rgb", sz
allocate(pixrgb(sz, sz))
! pixrgb = 0
do ix=1, sz
do iy=1, sz
pixrgb(ix, iy)%r = ix
pixrgb(ix, iy)%g = 0
pixrgb(ix, iy)%b = iy
end do
end do
call rgbpix_spit_as_pnm(pixrgb, "rgb.pnm")
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
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
2022-12-01 12:03:22 +01:00
call spit_as_pgm_16 (greymap, 'a.pgm')
call spit_as_pgm_eq (greymap, 'b.pgm')
call spit_as_pgm_8 (greymap, 'c.pgm')
call new_spit_a (greymap, 'x.pgm')
2022-12-01 12:03:22 +01:00
end subroutine
end program
!-------------------------------------------------------------------