-
Lionel GUEZ authoredLionel GUEZ authored
spher_polygon_area.f90 786 B
module spher_polygon_area_m
implicit none
contains
pure real function spher_polygon_area(p)
! Assuming p is a polygon in longitude, latitude, compute the area
! of a polygon in longitude, sin(latitude) with the same
! vertices. Result in m2.
! Libraries:
use gpc_f, only: polygon
use spher_polyline_area_m, only: spher_polyline_area
type(polygon), intent(in):: p ! in rad
! Local:
integer i
real parts_area(p%nparts) ! (positive) area of each part, in m2
!------------------------------------------------------
forall(i = 1:p%nparts) parts_area(i) = spher_polyline_area(p%part(i))
spher_polygon_area = sum(merge(- parts_area, parts_area, p%hole))
end function spher_polygon_area
end module spher_polygon_area_m