m_get_mod_grid.f90 8.2 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227
  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_get_mod_grid
  10. ! The reading of depths is not needed for assimilation of sea-ice data
  11. ! but left here for potential future use. And to retain the calling format.
  12. use netcdf
  13. use qmpi
  14. private handle_err
  15. contains
  16. subroutine get_mod_grid(modlon,modlat,depths,mindx,meandx,nx,ny)
  17. implicit none
  18. ! In/out
  19. integer, intent(in) :: nx,ny ! 182, resp. 149
  20. real, dimension(nx,ny), intent(out) :: modlon, modlat, depths
  21. real, intent(out) :: mindx, meandx
  22. ! NetCDF vars
  23. integer ncid, varID, error, ncid_mask, ncid_zgr
  24. character(len=80), parameter :: maskfile = 'mask.nc' !hc!
  25. character(len=80), parameter :: meshfile_hgr = 'mesh_hgr.nc' !hc!
  26. character(len=80), parameter :: meshfile_zgr = 'mesh_zgr.nc' !hc!
  27. logical ex
  28. ! Variables for mindx ! uncomment whatever is needed
  29. real, allocatable, dimension(:,:) :: e1t, e2t!, e1u, e2u, e1v, e2v, e1f, e2f
  30. real, allocatable, dimension(:,:) :: tmask!, umask, vmask, fmask
  31. ! check the netCDF file exists
  32. inquire(file=meshfile_hgr, exist=ex)
  33. if (.not.ex) then
  34. if (master) print *, '(get_mod_grid): file does not exist: '//trim(meshfile_hgr)
  35. call stop_mpi()
  36. end if
  37. ! open the netCDF file
  38. error = nf90_open(trim(maskfile),nf90_NoWrite,ncid_mask)
  39. if (error.ne.nf90_noerr) call handle_err(error, "opening")
  40. error = nf90_open(trim(meshfile_hgr),nf90_NoWrite,ncid)
  41. if (error.ne.nf90_noerr) call handle_err(error, "opening")
  42. error = nf90_open(trim(meshfile_zgr),nf90_NoWrite,ncid_zgr)
  43. if (error.ne.nf90_noerr) call handle_err(error, "opening")
  44. ! Longitude
  45. ! Find VarID
  46. !in NEMO mesh grid, lon and lat = GLAMT and GPHIT
  47. !error = nf90_inq_varid(ncid, 'nav_lon', varID)
  48. error = nf90_inq_varid(ncid, 'glamt', varID)
  49. if (error.ne.nf90_noerr) call handle_err(error, "inquiring varID modlon")
  50. ! Get values of variable
  51. error = nf90_get_var(ncid, varID, modlon)
  52. if (error.ne.nf90_noerr) call handle_err(error, "getting variable modlon")
  53. ! Latitude
  54. ! Find VarID
  55. !in NEMO mesh grid, lon and lat = GLAMT and GPHIT
  56. ! error = nf90_inq_varid(ncid, 'nav_lat', varID)
  57. error = nf90_inq_varid(ncid, 'gphit', varID)
  58. if (error.ne.nf90_noerr) call handle_err(error, "inquiring varID modlat")
  59. ! Get values of variable
  60. error = nf90_get_var(ncid, varID, modlat)
  61. if (error.ne.nf90_noerr) call handle_err(error, "getting variable modlat")
  62. ! Depths:
  63. ! Find VarID
  64. error = nf90_inq_varid(ncid_zgr, 'gdept_0', varID)
  65. if (error.ne.nf90_noerr) call handle_err(error, "inquiring varID depths")
  66. ! Get values of variable
  67. error = nf90_get_var(ncid_zgr, varID, depths)
  68. if (error.ne.nf90_noerr) call handle_err(error, "getting variable depths")
  69. ! mindx: Smallest horizontal grid spacing. Requires some 'math'.
  70. ! Load grid spacing and corresponding masks
  71. allocate( e1t(nx,ny), e2t(nx,ny) )
  72. !allocate( e1u(nx,ny), e2u(nx,ny) ) ! In case those variables are ...
  73. !allocate( e1v(nx,ny), e2v(nx,ny) ) ! ... needed, feel free ...
  74. !allocate( e1f(nx,ny), e2f(nx,ny) ) ! ... to uncomment.
  75. allocate( tmask(nx,ny) ) ! umask(nx,ny), vmask(nx,ny), fmask(nx,ny)
  76. ! Get e1t, e1u, e1v, e1f, e2t, e2u, e2v, and e2f
  77. error = nf90_inq_varid(ncid, 'e1t', varID) ; if (error.ne.nf90_noerr) call handle_err(error, "inquiring varID")
  78. error = nf90_get_var(ncid, varID, e1t) ; if (error.ne.nf90_noerr) call handle_err(error, "getting variable")
  79. error = nf90_inq_varid(ncid, 'e2t', varID) ; if (error.ne.nf90_noerr) call handle_err(error, "inquiring varID")
  80. error = nf90_get_var(ncid, varID, e2t) ; if (error.ne.nf90_noerr) call handle_err(error, "getting variable")
  81. !error = nf90_inq_varid(ncid, 'e1u', varID) ; if (error.ne.nf90_noerr) call handle_err(error, "inquiring varID")
  82. !error = nf90_get_var(ncid, varID, e1u) ; if (error.ne.nf90_noerr) call handle_err(error, "getting variable")
  83. !error = nf90_inq_varid(ncid, 'e2u', varID) ; if (error.ne.nf90_noerr) call handle_err(error, "inquiring varID")
  84. !error = nf90_get_var(ncid, varID, e2u) ; if (error.ne.nf90_noerr) call handle_err(error, "getting variable")
  85. !error = nf90_inq_varid(ncid, 'e1v', varID) ; if (error.ne.nf90_noerr) call handle_err(error, "inquiring varID")
  86. !error = nf90_get_var(ncid, varID, e1v) ; if (error.ne.nf90_noerr) call handle_err(error, "getting variable")
  87. !error = nf90_inq_varid(ncid, 'e2v', varID) ; if (error.ne.nf90_noerr) call handle_err(error, "inquiring varID")
  88. !error = nf90_get_var(ncid, varID, e2v) ; if (error.ne.nf90_noerr) call handle_err(error, "getting variable")
  89. !error = nf90_inq_varid(ncid, 'e1f', varID) ; if (error.ne.nf90_noerr) call handle_err(error, "inquiring varID")
  90. !error = nf90_get_var(ncid, varID, e1f) ; if (error.ne.nf90_noerr) call handle_err(error, "getting variable")
  91. !error = nf90_inq_varid(ncid, 'e2f', varID) ; if (error.ne.nf90_noerr) call handle_err(error, "inquiring varID")
  92. !error = nf90_get_var(ncid, varID, e2f) ; if (error.ne.nf90_noerr) call handle_err(error, "getting variable")
  93. ! Get tmask, umask, vmask, fmask !!! only first level of 3d-nc-var fits into local var. It's all we need.
  94. error = nf90_inq_varid(ncid_mask, 'tmask', varID) ; if (error.ne.nf90_noerr) call handle_err(error, "inquiring varID")
  95. error = nf90_get_var(ncid_mask, varID, tmask) ; if (error.ne.nf90_noerr) call handle_err(error, "getting variable")
  96. !error = nf90_inq_varid(ncid, 'umask', varID) ; if (error.ne.nf90_noerr) call handle_err(error, "inquiring varID")
  97. !error = nf90_get_var(ncid, varID, umask) ; if (error.ne.nf90_noerr) call handle_err(error, "getting variable")
  98. !error = nf90_inq_varid(ncid, 'vmask', varID) ; if (error.ne.nf90_noerr) call handle_err(error, "inquiring varID")
  99. !error = nf90_get_var(ncid, varID, vmask) ; if (error.ne.nf90_noerr) call handle_err(error, "getting variable")
  100. !error = nf90_inq_varid(ncid, 'fmask', varID) ; if (error.ne.nf90_noerr) call handle_err(error, "inquiring varID")
  101. !error = nf90_get_var(ncid, varID, fmask) ; if (error.ne.nf90_noerr) call handle_err(error, "getting variable")
  102. ! Smart use of min/maxval
  103. ! Find absolute minimum
  104. mindx = min(minval(e1t, tmask>0.5), minval(e2t, tmask>0.5))!, &
  105. ! minval(e1u, umask>0.5), minval(e2u, umask>0.5), &
  106. ! minval(e1v, vmask>0.5), minval(e2v, vmask>0.5), &
  107. ! minval(e1f, fmask>0.5), minval(e2f, fmask>0.5) )
  108. if (master) then
  109. print *,'(get_mod_grid) MINIMUM grid size from mesh_mask : ', mindx
  110. end if
  111. ! Find mean horizontal distance
  112. meandx = (sum(e1t,mask=tmask>0.5) + sum(e2t,mask=tmask>0.5) ) &
  113. / count(tmask>0.5)
  114. if (master) then
  115. print *,'(get_mod_grid) MEAN grid size from mesh_mask: ', meandx
  116. end if
  117. ! Safety check .. inherited from KAL
  118. if (mindx<2000.) then
  119. if (master) print *,'(get_mod_grid) min grid size lower than safety threshold - fix if you want'
  120. call stop_mpi()
  121. end if
  122. ! Safety check .. This one is not that critical so the value is set high
  123. if (mindx>500000.) then
  124. if (master) print *,'(get_mod_grid) min grid size higher than safety threshold - fix if you want'
  125. call stop_mpi()
  126. end if
  127. ! Close file
  128. error = nf90_close(ncid) ! close netCDF dataset
  129. if (error.ne.nf90_noerr) call handle_err(error, "closing")
  130. error = nf90_close(ncid_mask) ! close netCDF dataset
  131. if (error.ne.nf90_noerr) call handle_err(error, "closing")
  132. error = nf90_close(ncid_zgr) ! close netCDF dataset
  133. if (error.ne.nf90_noerr) call handle_err(error, "closing")
  134. end subroutine get_mod_grid
  135. subroutine handle_err(status, infomsg)
  136. integer, intent ( in) :: status
  137. character(len = *), intent ( in), optional :: infomsg
  138. if(status /= nf90_noerr) then
  139. if (master) then
  140. if (present(infomsg)) then
  141. print *, 'Error while '//infomsg//' - '//trim(nf90_strerror(status))
  142. else
  143. print *, trim(nf90_strerror(status))
  144. endif ! opt arg
  145. print *,'(get_mod_grid)'
  146. endif ! only master outputs
  147. call stop_mpi()
  148. end if ! check error status
  149. end subroutine handle_err
  150. end module m_get_mod_grid