Fortraneries/GrafAnim/readpicz.f90

60 lines
1.3 KiB
Fortran

program readpicz
use pixrgb
implicit none
integer :: nbarg
integer :: param0 = 10
character(len=256) :: arg
! integer :: foo, bar
integer :: width = 640
integer :: height = 480
integer :: x, y, r, g, b
integer :: errcode
character (len=280) :: filename
type(t_pixrgb), allocatable :: pix(:,:)
filename = "out.pnm"
nbarg = IARGC()
if (nbarg .GT. 0) then
call GETARG(1, arg)
! write (0, '(A40, A5)') "argument = ", arg
read (arg, *) param0
endif
allocate(pix(width, height))
do
!----- get a pixel
read(5, *, iostat=errcode) x, y, r, g, b
! print *, x, y
if (0 .NE. errcode) then
write(0, *) "iostat", errcode
exit
endif
if (mod(y, 2) .EQ. 1) then
pix(x+1, y+1)%r = g * 200
pix(x+1, y+1)%g = b * 200
pix(x+1, y+1)%b = r * 200
else
pix(x+1, y+1)%r = g * 200
pix(x+1, y+1)%g = r * 200
pix(x+1, y+1)%b = b * 200
endif
enddo
call rgbpix_spit_as_pnm_16(pix, trim(filename))
contains
! ----------------------------------------------------------
! ----------------------------------------------------------
end program