obs_read_altbias.F90 6.7 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216
  1. MODULE obs_read_altbias
  2. !!======================================================================
  3. !! *** MODULE obs_readaltbias ***
  4. !! Observation diagnostics: Read the bias for SLA data
  5. !!======================================================================
  6. !!----------------------------------------------------------------------
  7. !! obs_rea_altbias : Driver for reading altimeter bias
  8. !!----------------------------------------------------------------------
  9. !! * Modules used
  10. USE par_kind, ONLY : & ! Precision variables
  11. & wp, &
  12. & dp, &
  13. & sp
  14. USE par_oce, ONLY : & ! Domain parameters
  15. & jpi, &
  16. & jpj, &
  17. & jpim1
  18. USE in_out_manager, ONLY : & ! I/O manager
  19. & lwp, &
  20. & numout
  21. USE obs_surf_def ! Surface observation definitions
  22. USE dom_oce, ONLY : & ! Domain variables
  23. & tmask, &
  24. & tmask_i, &
  25. & e1t, &
  26. & e2t, &
  27. & gphit
  28. USE oce, ONLY : & ! Model variables
  29. & sshn
  30. USE obs_inter_h2d
  31. USE obs_utils ! Various observation tools
  32. USE obs_inter_sup
  33. USE wrk_nemo ! Memory Allocation
  34. IMPLICIT NONE
  35. !! * Routine accessibility
  36. PRIVATE
  37. PUBLIC obs_rea_altbias ! Read the altimeter bias
  38. !!----------------------------------------------------------------------
  39. !! NEMO/OPA 3.3 , NEMO Consortium (2010)
  40. !! $Id: obs_read_altbias.F90 3294 2012-01-28 16:44:18Z rblod $
  41. !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt)
  42. !!----------------------------------------------------------------------
  43. CONTAINS
  44. SUBROUTINE obs_rea_altbias( kslano, sladata, k2dint, bias_file )
  45. !!---------------------------------------------------------------------
  46. !!
  47. !! *** ROUTINE obs_rea_altbias ***
  48. !!
  49. !! ** Purpose : Read from file the bias data
  50. !!
  51. !! ** Method :
  52. !!
  53. !! ** Action :
  54. !!
  55. !! References :
  56. !!
  57. !! History :
  58. !! ! : 2008-02 (D. Lea) Initial version
  59. !!----------------------------------------------------------------------
  60. !! * Modules used
  61. USE iom
  62. !
  63. !! * Arguments
  64. INTEGER, INTENT(IN) :: kslano ! Number of SLA Products
  65. TYPE(obs_surf), DIMENSION(kslano), INTENT(INOUT) :: &
  66. & sladata ! SLA data
  67. INTEGER, INTENT(IN) :: k2dint
  68. CHARACTER(LEN=128) :: bias_file
  69. !! * Local declarations
  70. CHARACTER(LEN=12), PARAMETER :: cpname = 'obs_rea_altbias'
  71. INTEGER :: jslano ! Data set loop variable
  72. INTEGER :: jobs ! Obs loop variable
  73. INTEGER :: jpialtbias ! Number of grid point in latitude for the bias
  74. INTEGER :: jpjaltbias ! Number of grid point in longitude for the bias
  75. INTEGER :: iico ! Grid point indicies
  76. INTEGER :: ijco
  77. INTEGER :: i_nx_id ! Index to read the NetCDF file
  78. INTEGER :: i_ny_id !
  79. INTEGER :: i_file_id !
  80. INTEGER :: i_var_id
  81. REAL(wp), DIMENSION(1) :: &
  82. & zext, &
  83. & zobsmask
  84. REAL(wp), DIMENSION(2,2,1) :: &
  85. & zweig
  86. REAL(wp), DIMENSION(:,:,:), ALLOCATABLE :: &
  87. & zmask, &
  88. & zbias, &
  89. & zglam, &
  90. & zgphi
  91. REAL(wp), POINTER, DIMENSION(:,:) :: z_altbias
  92. REAL(wp) :: zlam
  93. REAL(wp) :: zphi
  94. INTEGER, DIMENSION(:,:,:), ALLOCATABLE :: &
  95. & igrdi, &
  96. & igrdj
  97. INTEGER :: numaltbias
  98. CALL wrk_alloc(jpi,jpj,z_altbias)
  99. IF(lwp)WRITE(numout,*)
  100. IF(lwp)WRITE(numout,*) ' obs_rea_altbias : '
  101. IF(lwp)WRITE(numout,*) ' ------------- '
  102. IF(lwp)WRITE(numout,*) ' Read altimeter bias'
  103. ! Open the file
  104. z_altbias(:,:)=0.0_wp
  105. numaltbias=0
  106. IF(lwp)WRITE(numout,*) 'Opening ',bias_file
  107. CALL iom_open( bias_file, numaltbias, ldstop=.FALSE. )
  108. IF (numaltbias .GT. 0) THEN
  109. ! Get the Alt bias data
  110. CALL iom_get( numaltbias, jpdom_data, 'altbias', z_altbias(:,:), 1 )
  111. ! Close the file
  112. CALL iom_close(numaltbias)
  113. ELSE
  114. IF(lwp)WRITE(numout,*) 'no file found'
  115. ENDIF
  116. ! Intepolate the bias already on the model grid at the observation point
  117. DO jslano = 1, kslano
  118. ALLOCATE( &
  119. & igrdi(2,2,sladata(jslano)%nsurf), &
  120. & igrdj(2,2,sladata(jslano)%nsurf), &
  121. & zglam(2,2,sladata(jslano)%nsurf), &
  122. & zgphi(2,2,sladata(jslano)%nsurf), &
  123. & zmask(2,2,sladata(jslano)%nsurf), &
  124. & zbias(2,2,sladata(jslano)%nsurf) &
  125. & )
  126. DO jobs = 1, sladata(jslano)%nsurf
  127. igrdi(1,1,jobs) = sladata(jslano)%mi(jobs)-1
  128. igrdj(1,1,jobs) = sladata(jslano)%mj(jobs)-1
  129. igrdi(1,2,jobs) = sladata(jslano)%mi(jobs)-1
  130. igrdj(1,2,jobs) = sladata(jslano)%mj(jobs)
  131. igrdi(2,1,jobs) = sladata(jslano)%mi(jobs)
  132. igrdj(2,1,jobs) = sladata(jslano)%mj(jobs)-1
  133. igrdi(2,2,jobs) = sladata(jslano)%mi(jobs)
  134. igrdj(2,2,jobs) = sladata(jslano)%mj(jobs)
  135. END DO
  136. CALL obs_int_comm_2d( 2, 2, sladata(jslano)%nsurf, &
  137. & igrdi, igrdj, glamt, zglam )
  138. CALL obs_int_comm_2d( 2, 2, sladata(jslano)%nsurf, &
  139. & igrdi, igrdj, gphit, zgphi )
  140. CALL obs_int_comm_2d( 2, 2, sladata(jslano)%nsurf, &
  141. & igrdi, igrdj, tmask(:,:,1), zmask )
  142. CALL obs_int_comm_2d( 2, 2, sladata(jslano)%nsurf, &
  143. & igrdi, igrdj, z_altbias, zbias )
  144. DO jobs = 1, sladata(jslano)%nsurf
  145. zlam = sladata(jslano)%rlam(jobs)
  146. zphi = sladata(jslano)%rphi(jobs)
  147. iico = sladata(jslano)%mi(jobs)
  148. ijco = sladata(jslano)%mj(jobs)
  149. CALL obs_int_h2d_init( 1, 1, k2dint, zlam, zphi, &
  150. & zglam(:,:,jobs), zgphi(:,:,jobs), &
  151. & zmask(:,:,jobs), zweig, zobsmask )
  152. CALL obs_int_h2d( 1, 1, &
  153. & zweig, zbias(:,:,jobs), zext )
  154. ! adjust mdt with bias field
  155. sladata(jslano)%rext(jobs,2) = &
  156. sladata(jslano)%rext(jobs,2) - zext(1)
  157. END DO
  158. DEALLOCATE( &
  159. & igrdi, &
  160. & igrdj, &
  161. & zglam, &
  162. & zgphi, &
  163. & zmask, &
  164. & zbias &
  165. & )
  166. END DO
  167. CALL wrk_dealloc(jpi,jpj,z_altbias)
  168. END SUBROUTINE obs_rea_altbias
  169. END MODULE obs_read_altbias