Fortraneries/Modules/pixrgb.f90

67 lines
1.7 KiB
Fortran
Raw Normal View History

2022-12-16 19:26:54 +01:00
!-
! This module try to write PGM complient gray level files
!-
module pixrgb
implicit none
!-----------------------------------------------------------------------
!-
! definition of structures
!-
type t_pixrgb
integer :: r, g, b
integer :: alpha = 0
end type
!-------------------------------------------------------------------
contains
!-------------------------------------------------------------------
!-
2022-12-17 12:09:57 +01:00
subroutine rgbpix_spit_as_pnm_8(pic, fname)
2022-12-16 19:26:54 +01:00
type(t_pixrgb), intent(in) :: pic(:,:)
character (len=*), intent(in) :: fname
integer :: io, ix, iy
open(newunit=io, file=fname)
write (io, '(a2)') "P3"
2022-12-17 12:09:57 +01:00
write (io, '("# rgbpix_spit_as_pnm_8")')
2022-12-16 19:26:54 +01:00
write (io, '(i0," ",i0)') size(pic, 1), size(pic, 2)
write (io, '(i0)') 255
do iy=1, ubound(pic, 2)
do ix=1, ubound(pic, 1)
2022-12-17 12:09:57 +01:00
write(io, "(3I4)") pic(ix, iy)%r, pic(ix, iy)%g, pic(ix, iy)%b
enddo
enddo
close(unit=io)
end subroutine
!-------------------------------------------------------------------
!-
subroutine rgbpix_spit_as_pnm_16(pic, fname)
type(t_pixrgb), intent(in) :: pic(:,:)
character (len=*), intent(in) :: fname
integer :: io, ix, iy
open(newunit=io, file=fname)
write (io, '(a2)') "P3"
write (io, '("# rgbpix_spit_as_pnm_16")')
write (io, '(i0," ",i0)') size(pic, 1), size(pic, 2)
write (io, '(i0)') 65535
do iy=1, ubound(pic, 2)
do ix=1, ubound(pic, 1)
write(io, "(3I6)") pic(ix, iy)%r, pic(ix, iy)%g, pic(ix, iy)%b
2022-12-16 19:26:54 +01:00
enddo
enddo
close(unit=io)
end subroutine
!-------------------------------------------------------------------
end module