! the following are to be used in python: subroutine mkmap(code, x, y, m, n, xout, yout, nout, xs, ys, & & nrx, nry, iflag, nrin, w, iref, covered, xymiss) use interp_module, only: mkmap1 => mkmap implicit none integer , dimension(m, n) , intent(in) :: code real*8 , dimension(m, n) , intent(in) :: x real*8 , dimension(m, n) , intent(in) :: y integer , intent(in) :: m integer , intent(in) :: n real*8 , dimension(nout) , intent(out) :: xout real*8 , dimension(nout) , intent(out) :: yout integer , intent(in) :: nout real*8 , dimension(nout) , intent(out) :: xs real*8 , dimension(nout) , intent(out) :: ys integer , dimension(nout) , intent(out) :: nrx integer , dimension(nout) , intent(out) :: nry integer , dimension(nout) , intent(out) :: iflag integer , dimension(nout) , intent(out) :: nrin real*8 , dimension(4 , nout), intent(out) :: w integer , dimension(4 , nout), intent(out) :: iref integer , dimension(nout) , intent(out) :: covered ! 0: target point is not covered by source grid (default) ! 1: target point is covered by valid points of source grid ! -1: target point is covered by invalid points of source grid real*8 , intent(in) :: xymiss ! missing value in grid 1 call mkmap1 (code, x, y, m, n, xout, yout, nout, xs, ys, & & nrx, nry, iflag, nrin, w, iref, 0, covered, xymiss) end subroutine mkmap subroutine grmap(f1, n1, f2, n2, iref, w, np, iprint) use interp_module, only: grmapx => grmap implicit none ! ! Global variables ! real*8 , dimension(n1) , intent(in) :: f1 integer , intent(in) :: n1 real*8 , dimension(n2) , intent(out) :: f2 integer , intent(in) :: n2 integer, dimension(np, n2), intent(in) :: iref real*8 , dimension(np, n2), intent(in) :: w integer , intent(in) :: np integer , intent(in) :: iprint call grmapx(f1, n1, f2, n2, iref, w, np, iprint) end subroutine grmap subroutine grmap2(f1, cellsz1i, n1, f2, cellsz2, n2, iref, w, np) use interp_module, only: grmap2x => grmap2 implicit none ! ! Global variables ! real*8 , dimension(n1) , intent(inout) :: f1 real*8 , dimension(n1) , intent(in) :: cellsz1i !array with 1/cell size integer , intent(in) :: n1 real*8 , dimension(n2) , intent(in) :: f2 real*8 , intent(in) :: cellsz2 integer , intent(in) :: n2 integer, dimension(np, n2), intent(in) :: iref real*8 , dimension(np, n2), intent(in) :: w integer , intent(in) :: np call grmap2x(f1, cellsz1i, n1, f2, cellsz2, n2, iref, w, np) end subroutine grmap2