m_bilincoeff.f90 3.2 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161
  1. # 0 "<stdin>"
  2. # 0 "<built-in>"
  3. # 0 "<command-line>"
  4. # 1 "/usr/include/stdc-predef.h" 1 3 4
  5. # 17 "/usr/include/stdc-predef.h" 3 4
  6. # 2 "<command-line>" 2
  7. # 1 "<stdin>"
  8. # 10 "<stdin>"
  9. module m_bilincoeff
  10. use m_oldtonew
  11. implicit none
  12. contains
  13. ! This subroutine uses bilinear interpolation to interpolate the field
  14. ! computed by the model (MICOM) to the position defined by lon, lat
  15. ! The output is the interpolation coeffisients a[1-4]
  16. ! NB NO locations on land.
  17. !
  18. subroutine bilincoeff(glon, glat, nx, ny, lon, lat, ipiv, jpiv, a1, a2, a3, a4)
  19. real, intent(in) :: glon(nx, ny), glat(nx, ny)
  20. integer, intent(in) :: nx ,ny
  21. real, intent(in) :: lon, lat
  22. integer, intent(in) :: ipiv, jpiv
  23. real, intent(out) :: a1, a2, a3, a4
  24. real :: t, u
  25. real :: lat1, lon1, lat2, lon2, latn, lonn
  26. call oldtonew(glat(ipiv, jpiv), glon(ipiv, jpiv), lat1, lon1)
  27. call oldtonew(glat(ipiv + 1, jpiv + 1), glon(ipiv + 1, jpiv + 1), lat2, lon2)
  28. call oldtonew(lat, lon, latn, lonn)
  29. t = (lonn - lon1) / (lon2 - lon1)
  30. u = (latn - lat1) / (lat2 - lat1)
  31. if (t < -0.1 .or. t > 1.1 .or. u < -0.1 .or. u > 1.1) then
  32. print *, 'ERROR: bilincoeff(): t, u = ', t, u, 'for lon, lat =', lon, lat
  33. stop
  34. end if
  35. a1 = (1.0 - t) * (1.0 - u)
  36. a2 = t * (1.0 - u)
  37. a3 = t * u
  38. a4 = (1.0 - t) * u
  39. end subroutine bilincoeff
  40. subroutine bilincoeff1(glon, glat, nx, ny, lon, lat, ipiv, jpiv, a1, a2, a3, a4)
  41. real, intent(in) :: glon(nx, ny), glat(nx, ny)
  42. integer, intent(in) :: nx ,ny
  43. real, intent(in) :: lon, lat
  44. integer, intent(in) :: ipiv, jpiv
  45. real, intent(out) :: a1, a2, a3, a4
  46. real :: xx(4), yy(4)
  47. real :: t, u
  48. xx(1) = glon(ipiv, jpiv)
  49. xx(2) = glon(ipiv + 1, jpiv)
  50. xx(3) = glon(ipiv + 1, jpiv + 1)
  51. xx(4) = glon(ipiv, jpiv + 1)
  52. yy(1) = glat(ipiv, jpiv)
  53. yy(2) = glat(ipiv + 1, jpiv)
  54. yy(3) = glat(ipiv + 1, jpiv + 1)
  55. yy(4) = glat(ipiv, jpiv + 1)
  56. call xy2fij(lon, lat, xx, yy, t, u)
  57. if (t < 0 .or. t > 1 .or. u < 0 .or. u > 1) then
  58. print *, 'ERROR: bilincoeff(): t, u = ', t, u, 'for lon, lat =', lon, lat
  59. ! stop
  60. end if
  61. a1 = (1.0 - t) * (1.0 - u)
  62. a2 = t * (1.0 - u)
  63. a3 = t * u
  64. a4 = (1.0 - t) * u
  65. end subroutine bilincoeff1
  66. subroutine xy2fij(x, y, xx, yy, fi, fj)
  67. real, intent(in) :: x, y
  68. real, intent(in) :: xx(4), yy(4)
  69. real, intent(out) :: fi, fj
  70. real :: a, b, c, d, e, f, g, h
  71. real :: aa, bb, cc
  72. real :: d1, d2
  73. a = xx(1) - xx(2) - xx(4) + xx(3)
  74. b = xx(2) - xx(1)
  75. c = xx(4) - xx(1)
  76. d = xx(1)
  77. e = yy(1) - yy(2) - yy(4) + yy(3)
  78. f = yy(2) - yy(1)
  79. g = yy(4) - yy(1)
  80. h = yy(1)
  81. aa = a * f - b * e;
  82. bb = e * x - a * y + a * h - d * e + c * f - b * g;
  83. cc = g * x - c * y + c * h - d * g;
  84. if (abs(aa) < 1d-5) then
  85. fi = -cc / bb * (1.0d0 + aa * cc / bb / bb);
  86. else
  87. fi = (-bb - sqrt(bb * bb - 4.0d0 * aa * cc)) / (2.0d0 * aa);
  88. end if
  89. d1 = a * fi + c
  90. d2 = e * fi + g
  91. if (abs(d2) > abs(d1)) then
  92. fj = (y - f * fi - h) / d2
  93. else
  94. fj = (x - b * fi - d) / d1
  95. end if
  96. end subroutine xy2fij
  97. end module m_bilincoeff