Compare commits
3 Commits
7ee4fefaa4
...
f95dc7ed2a
Author | SHA1 | Date | |
---|---|---|---|
|
f95dc7ed2a | ||
|
2d7739dd1d | ||
|
9c148c3d7e |
@ -37,7 +37,8 @@ contains
|
|||||||
pixrgb(ix, iy)%b = iy
|
pixrgb(ix, iy)%b = iy
|
||||||
end do
|
end do
|
||||||
end do
|
end do
|
||||||
call rgbpix_spit_as_pnm_8(pixrgb, "rgb.pnm")
|
call rgbpix_spit_as_pnm_8(pixrgb, "rgb8.pnm")
|
||||||
|
call rgbpix_spit_as_pnm_16(pixrgb, "rgb16.pnm")
|
||||||
deallocate(pixrgb)
|
deallocate(pixrgb)
|
||||||
|
|
||||||
end subroutine
|
end subroutine
|
||||||
@ -58,8 +59,8 @@ contains
|
|||||||
value = value + increment
|
value = value + increment
|
||||||
enddo
|
enddo
|
||||||
enddo
|
enddo
|
||||||
call spit_as_pgm_16 (greymap, 'a.pnm')
|
! call spit_as_pgm_16 (greymap, 'a.pnm')
|
||||||
call spit_as_pgm_eq (greymap, 'b.pnm')
|
! call spit_as_pgm_eq (greymap, 'b.pnm')
|
||||||
call spit_as_pgm_8 (greymap, 'c.pnm')
|
call spit_as_pgm_8 (greymap, 'c.pnm')
|
||||||
call new_spit_a (greymap, 'x.pnm')
|
call new_spit_a (greymap, 'x.pnm')
|
||||||
end subroutine
|
end subroutine
|
||||||
|
@ -28,6 +28,25 @@ module mathstuff2
|
|||||||
|
|
||||||
end subroutine
|
end subroutine
|
||||||
|
|
||||||
|
! ----------------------------------------------------------------
|
||||||
|
|
||||||
|
logical function diff_sign(a, b)
|
||||||
|
integer, intent(in) :: a, b
|
||||||
|
|
||||||
|
! write(0, *) "diff_sign", a, b
|
||||||
|
if ( (a .lt. 0) .and. (b .ge. 0) ) then
|
||||||
|
diff_sign = .TRUE.
|
||||||
|
return
|
||||||
|
endif
|
||||||
|
if ( (a .ge. 0) .and. (b .lt. 0) ) then
|
||||||
|
diff_sign = .TRUE.
|
||||||
|
return
|
||||||
|
endif
|
||||||
|
diff_sign = .FALSE.
|
||||||
|
|
||||||
|
end function
|
||||||
|
|
||||||
|
|
||||||
! ----------------------------------------------------------------
|
! ----------------------------------------------------------------
|
||||||
end module mathstuff2
|
end module mathstuff2
|
||||||
|
|
||||||
|
@ -77,7 +77,8 @@ subroutine rgbpix_spit_as_pnm_8(pic, fname)
|
|||||||
|
|
||||||
do iy=1, ubound(pic, 2)
|
do iy=1, ubound(pic, 2)
|
||||||
do ix=1, ubound(pic, 1)
|
do ix=1, ubound(pic, 1)
|
||||||
write(io, "(3I5)") pic(ix, iy)%r, pic(ix, iy)%g, pic(ix, iy)%b
|
write(io, "(I0,' ', I0,' ',I0)") &
|
||||||
|
pic(ix, iy)%r, pic(ix, iy)%g, pic(ix, iy)%b
|
||||||
enddo
|
enddo
|
||||||
enddo
|
enddo
|
||||||
close(unit=io)
|
close(unit=io)
|
||||||
@ -102,7 +103,8 @@ subroutine rgbpix_spit_as_pnm_16(pic, fname)
|
|||||||
|
|
||||||
do iy=1, ubound(pic, 2)
|
do iy=1, ubound(pic, 2)
|
||||||
do ix=1, ubound(pic, 1)
|
do ix=1, ubound(pic, 1)
|
||||||
write(io, "(3I6)") pic(ix, iy)%r, pic(ix, iy)%g, pic(ix, iy)%b
|
write(io, "(I0,' ', I0,' ',I0)") &
|
||||||
|
pic(ix, iy)%r, pic(ix, iy)%g, pic(ix, iy)%b
|
||||||
enddo
|
enddo
|
||||||
enddo
|
enddo
|
||||||
close(unit=io)
|
close(unit=io)
|
||||||
|
Loading…
Reference in New Issue
Block a user