sbcapr.F90 9.1 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164
  1. MODULE sbcapr
  2. !!======================================================================
  3. !! *** MODULE sbcapr ***
  4. !! Surface module : atmospheric pressure forcing
  5. !!======================================================================
  6. !! History : 3.3 ! 2010-09 (J. Chanut, C. Bricaud, G. Madec) Original code
  7. !!----------------------------------------------------------------------
  8. !!----------------------------------------------------------------------
  9. !! sbc_apr : read atmospheric pressure in netcdf files
  10. !!----------------------------------------------------------------------
  11. USE dom_oce ! ocean space and time domain
  12. USE sbc_oce ! surface boundary condition
  13. USE dynspg_oce ! surface pressure gradient variables
  14. USE phycst ! physical constants
  15. USE fldread ! read input fields
  16. USE in_out_manager ! I/O manager
  17. USE lib_fortran ! distribued memory computing library
  18. USE iom ! IOM library
  19. USE lib_mpp ! MPP library
  20. IMPLICIT NONE
  21. PRIVATE
  22. PUBLIC sbc_apr ! routine called in sbcmod
  23. ! !!* namsbc_apr namelist (Atmospheric PRessure) *
  24. LOGICAL, PUBLIC :: ln_apr_obc !: inverse barometer added to OBC ssh data
  25. LOGICAL, PUBLIC :: ln_ref_apr !: ref. pressure: global mean Patm (F) or a constant (F)
  26. REAL(wp) :: rn_pref ! reference atmospheric pressure [N/m2]
  27. REAL(wp), ALLOCATABLE, SAVE, PUBLIC, DIMENSION(:,:) :: ssh_ib ! Inverse barometer now sea surface height [m]
  28. REAL(wp), ALLOCATABLE, SAVE, PUBLIC, DIMENSION(:,:) :: ssh_ibb ! Inverse barometer before sea surface height [m]
  29. REAL(wp), ALLOCATABLE, SAVE, PUBLIC, DIMENSION(:,:) :: apr ! atmospheric pressure at kt [N/m2]
  30. REAL(wp) :: tarea ! whole domain mean masked ocean surface
  31. REAL(wp) :: r1_grau ! = 1.e0 / (grav * rau0)
  32. TYPE(FLD), ALLOCATABLE, DIMENSION(:) :: sf_apr ! structure of input fields (file informations, fields read)
  33. !! * Substitutions
  34. # include "domzgr_substitute.h90"
  35. !!----------------------------------------------------------------------
  36. !! NEMO/OPA 4.0 , NEMO Consortium (2011)
  37. !! $Id: sbcapr.F90 2355 2015-05-20 07:11:50Z ufla $
  38. !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt)
  39. !!----------------------------------------------------------------------
  40. CONTAINS
  41. SUBROUTINE sbc_apr( kt )
  42. !!---------------------------------------------------------------------
  43. !! *** ROUTINE sbc_apr ***
  44. !!
  45. !! ** Purpose : read atmospheric pressure fields in netcdf files.
  46. !!
  47. !! ** Method : - Read namelist namsbc_apr
  48. !! - Read Patm fields in netcdf files
  49. !! - Compute reference atmospheric pressure
  50. !! - Compute inverse barometer ssh
  51. !! ** action : apr : atmospheric pressure at kt
  52. !! ssh_ib : inverse barometer ssh at kt
  53. !!---------------------------------------------------------------------
  54. INTEGER, INTENT(in):: kt ! ocean time step
  55. !!
  56. INTEGER :: ierror ! local integer
  57. INTEGER :: ios ! Local integer output status for namelist read
  58. !!
  59. CHARACTER(len=100) :: cn_dir ! Root directory for location of ssr files
  60. TYPE(FLD_N) :: sn_apr ! informations about the fields to be read
  61. !!
  62. NAMELIST/namsbc_apr/ cn_dir, sn_apr, ln_ref_apr, rn_pref, ln_apr_obc
  63. !!----------------------------------------------------------------------
  64. !
  65. !
  66. ! ! -------------------- !
  67. IF( kt == nit000 ) THEN ! First call kt=nit000 !
  68. ! ! -------------------- !
  69. REWIND( numnam_ref ) ! Namelist namsbc_apr in reference namelist : File for atmospheric pressure forcing
  70. READ ( numnam_ref, namsbc_apr, IOSTAT = ios, ERR = 901)
  71. 901 IF( ios /= 0 ) CALL ctl_nam ( ios , 'namsbc_apr in reference namelist', lwp )
  72. REWIND( numnam_cfg ) ! Namelist namsbc_apr in configuration namelist : File for atmospheric pressure forcing
  73. READ ( numnam_cfg, namsbc_apr, IOSTAT = ios, ERR = 902 )
  74. 902 IF( ios /= 0 ) CALL ctl_nam ( ios , 'namsbc_apr in configuration namelist', lwp )
  75. IF(lwm) WRITE ( numond, namsbc_apr )
  76. !
  77. ALLOCATE( sf_apr(1), STAT=ierror ) !* allocate and fill sf_sst (forcing structure) with sn_sst
  78. IF( ierror > 0 ) CALL ctl_stop( 'STOP', 'sbc_apr: unable to allocate sf_apr structure' )
  79. !
  80. CALL fld_fill( sf_apr, (/ sn_apr /), cn_dir, 'sbc_apr', 'Atmospheric pressure ', 'namsbc_apr' )
  81. ALLOCATE( sf_apr(1)%fnow(jpi,jpj,1) )
  82. IF( sn_apr%ln_tint ) ALLOCATE( sf_apr(1)%fdta(jpi,jpj,1,2) )
  83. ALLOCATE( ssh_ib(jpi,jpj) , ssh_ibb(jpi,jpj) )
  84. ALLOCATE( apr (jpi,jpj) )
  85. !
  86. IF(lwp) THEN !* control print
  87. WRITE(numout,*)
  88. WRITE(numout,*) ' Namelist namsbc_apr : Atmospheric PRessure as extrenal forcing'
  89. WRITE(numout,*) ' ref. pressure: global mean Patm (T) or a constant (F) ln_ref_apr = ', ln_ref_apr
  90. ENDIF
  91. !
  92. IF( ln_ref_apr ) THEN !* Compute whole inner domain mean masked ocean surface
  93. tarea = glob_sum( e1e2t(:,:) )
  94. IF(lwp) WRITE(numout,*) ' Variable ref. Patm computed over a ocean surface of ', tarea*1e-6, 'km2'
  95. ELSE
  96. IF(lwp) WRITE(numout,*) ' Reference Patm used : ', rn_pref, ' N/m2'
  97. ENDIF
  98. !
  99. r1_grau = 1.e0 / (grav * rau0) !* constant for optimization
  100. !
  101. ! !* control check
  102. IF ( ln_apr_obc ) THEN
  103. IF(lwp) WRITE(numout,*) ' Inverse barometer added to OBC ssh data'
  104. ENDIF
  105. IF( ( ln_apr_obc ) .AND. .NOT. lk_dynspg_ts ) &
  106. CALL ctl_stop( 'sbc_apr: use inverse barometer ssh at open boundary ONLY possible with time-splitting' )
  107. IF( ( ln_apr_obc ) .AND. .NOT. ln_apr_dyn ) &
  108. CALL ctl_stop( 'sbc_apr: use inverse barometer ssh at open boundary ONLY requires ln_apr_dyn=T' )
  109. ENDIF
  110. ! ! ========================== !
  111. IF( MOD( kt-1, nn_fsbc ) == 0 ) THEN ! At each sbc time-step !
  112. ! ! ===========+++============ !
  113. !
  114. IF( kt /= nit000 ) ssh_ibb(:,:) = ssh_ib(:,:) !* Swap of ssh_ib fields
  115. !
  116. CALL fld_read( kt, nn_fsbc, sf_apr ) !* input Patm provided at kt + nn_fsbc/2
  117. !
  118. ! !* update the reference atmospheric pressure (if necessary)
  119. IF( ln_ref_apr ) rn_pref = glob_sum( sf_apr(1)%fnow(:,:,1) * e1e2t(:,:) ) / tarea
  120. !
  121. ! !* Patm related forcing at kt
  122. ssh_ib(:,:) = - ( sf_apr(1)%fnow(:,:,1) - rn_pref ) * r1_grau ! equivalent ssh (inverse barometer)
  123. apr (:,:) = sf_apr(1)%fnow(:,:,1) ! atmospheric pressure
  124. !
  125. CALL iom_put( "ssh_ib", ssh_ib ) !* output the inverse barometer ssh
  126. ENDIF
  127. ! ! ---------------------------------------- !
  128. IF( kt == nit000 ) THEN ! set the forcing field at nit000 - 1 !
  129. ! ! ---------------------------------------- !
  130. ! !* Restart: read in restart file
  131. IF( ln_rstart .AND. iom_varid( numror, 'ssh_ibb', ldstop = .FALSE. ) > 0 ) THEN
  132. IF(lwp) WRITE(numout,*) 'sbc_apr: ssh_ibb read in the restart file'
  133. CALL iom_get( numror, jpdom_autoglo, 'ssh_ibb', ssh_ibb ) ! before inv. barometer ssh
  134. !
  135. ELSE !* no restart: set from nit000 values
  136. IF(lwp) WRITE(numout,*) 'sbc_apr: ssh_ibb set to nit000 values'
  137. ssh_ibb(:,:) = ssh_ib(:,:)
  138. ENDIF
  139. ENDIF
  140. ! ! ---------------------------------------- !
  141. IF( lrst_oce ) THEN ! Write in the ocean restart file !
  142. ! ! ---------------------------------------- !
  143. IF(lwp) WRITE(numout,*)
  144. IF(lwp) WRITE(numout,*) 'sbc_apr : ssh_ib written in ocean restart file at it= ', kt,' date= ', ndastp
  145. IF(lwp) WRITE(numout,*) '~~~~'
  146. CALL iom_rstput( kt, nitrst, numrow, 'ssh_ibb' , ssh_ib )
  147. ENDIF
  148. !
  149. END SUBROUTINE sbc_apr
  150. !!======================================================================
  151. END MODULE sbcapr