94 lines
		
	
	
		
			2.6 KiB
		
	
	
	
		
			Fortran
		
	
	
	
	
	
			
		
		
	
	
			94 lines
		
	
	
		
			2.6 KiB
		
	
	
	
		
			Fortran
		
	
	
	
	
	
!-
 | 
						|
!	This module try to write PNM complient RGB files
 | 
						|
!-
 | 
						|
module pixrgb
 | 
						|
    implicit none
 | 
						|
!-----------------------------------------------------------------------
 | 
						|
!-
 | 
						|
!      definition of structures
 | 
						|
!-
 | 
						|
type t_pixrgb
 | 
						|
  integer           :: r, g, b
 | 
						|
  integer           :: alpha = 0
 | 
						|
end type
 | 
						|
!-------------------------------------------------------------------
 | 
						|
contains
 | 
						|
!-------------------------------------------------------------------
 | 
						|
!-
 | 
						|
subroutine rgbpix_set_to_zero(pic)
 | 
						|
  type(t_pixrgb), intent(out)       ::  pic(:,:)
 | 
						|
  integer                           ::  ix, iy
 | 
						|
  do iy=1, ubound(pic, 2)
 | 
						|
    do ix=1, ubound(pic, 1)
 | 
						|
      pic(ix, iy)%r = 0
 | 
						|
      pic(ix, iy)%g = 0
 | 
						|
      pic(ix, iy)%b = 0
 | 
						|
    enddo
 | 
						|
  enddo
 | 
						|
end subroutine
 | 
						|
!-------------------------------------------------------------------
 | 
						|
!-
 | 
						|
!		NOT TESTED !!!
 | 
						|
!-
 | 
						|
subroutine rgb_pix_clamp_at_8(pic)
 | 
						|
  type(t_pixrgb), intent(inout)     ::  pic(:,:)
 | 
						|
  integer                           ::  ix, iy
 | 
						|
  do iy=1, ubound(pic, 2)
 | 
						|
    do ix=1, ubound(pic, 1)
 | 
						|
      pic(ix, iy)%r = max(0, min(pic(ix, iy)%r, 255))
 | 
						|
      pic(ix, iy)%g = max(0, min(pic(ix, iy)%g, 255))
 | 
						|
      pic(ix, iy)%b = max(0, min(pic(ix, iy)%b, 255))
 | 
						|
    enddo
 | 
						|
  enddo
 | 
						|
end subroutine
 | 
						|
!-------------------------------------------------------------------
 | 
						|
!-
 | 
						|
!          CAUTION: there was NO out-of-bounds check !
 | 
						|
!-
 | 
						|
subroutine rgbpix_spit_as_pnm_8(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_8")')
 | 
						|
  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)
 | 
						|
      write(io, "(3I5)") pic(ix, iy)%r, pic(ix, iy)%g, pic(ix, iy)%b
 | 
						|
    enddo
 | 
						|
  enddo
 | 
						|
  close(unit=io)
 | 
						|
 | 
						|
end subroutine
 | 
						|
!-------------------------------------------------------------------
 | 
						|
!-
 | 
						|
!          CAUTION: there was NO out-of-bounds check !
 | 
						|
!-
 | 
						|
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
 | 
						|
    enddo
 | 
						|
  enddo
 | 
						|
  close(unit=io)
 | 
						|
 | 
						|
end subroutine
 | 
						|
!-------------------------------------------------------------------
 | 
						|
end module |