New URL for NEMO forge!   http://forge.nemo-ocean.eu

Since March 2022 along with NEMO 4.2 release, the code development moved to a self-hosted GitLab.
This present forge is now archived and remained online for history.
sbcapr.F90 in NEMO/trunk/src/OCE/SBC – NEMO

source: NEMO/trunk/src/OCE/SBC/sbcapr.F90 @ 12377

Last change on this file since 12377 was 12377, checked in by acc, 4 years ago

The big one. Merging all 2019 developments from the option 1 branch back onto the trunk.

This changeset reproduces 2019/dev_r11943_MERGE_2019 on the trunk using a 2-URL merge
onto a working copy of the trunk. I.e.:

svn merge --ignore-ancestry \

svn+ssh://acc@forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/NEMO/trunk \
svn+ssh://acc@forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/NEMO/branches/2019/dev_r11943_MERGE_2019 ./

The --ignore-ancestry flag avoids problems that may otherwise arise from the fact that
the merge history been trunk and branch may have been applied in a different order but
care has been taken before this step to ensure that all applicable fixes and updates
are present in the merge branch.

The trunk state just before this step has been branched to releases/release-4.0-HEAD
and that branch has been immediately tagged as releases/release-4.0.2. Any fixes
or additions in response to tickets on 4.0, 4.0.1 or 4.0.2 should be done on
releases/release-4.0-HEAD. From now on future 'point' releases (e.g. 4.0.2) will
remain unchanged with periodic releases as needs demand. Note release-4.0-HEAD is a
transitional naming convention. Future full releases, say 4.2, will have a release-4.2
branch which fulfills this role and the first point release (e.g. 4.2.0) will be made
immediately following the release branch creation.

2020 developments can be started from any trunk revision later than this one.

  • Property svn:keywords set to Id
File size: 9.4 KB
Line 
1MODULE 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   !!----------------------------------------------------------------------
10   !!   sbc_apr        : read atmospheric pressure in netcdf files
11   !!----------------------------------------------------------------------
12   USE dom_oce         ! ocean space and time domain
13   USE sbc_oce         ! surface boundary condition
14   USE phycst          ! physical constants
15   !
16   USE fldread         ! read input fields
17   USE in_out_manager  ! I/O manager
18   USE lib_fortran     ! distribued memory computing library
19   USE iom             ! IOM library
20   USE lib_mpp         ! MPP library
21
22   IMPLICIT NONE
23   PRIVATE
24
25   PUBLIC   sbc_apr       ! routine called in sbcmod
26   PUBLIC   sbc_apr_init  ! routine called in sbcmod
27   
28   !                                          !!* namsbc_apr namelist (Atmospheric PRessure) *
29   LOGICAL, PUBLIC ::   ln_apr_obc = .false.   !: inverse barometer added to OBC ssh data
30   LOGICAL, PUBLIC ::   ln_ref_apr             !: ref. pressure: global mean Patm (F) or a constant (F)
31   REAL(wp)        ::   rn_pref                !  reference atmospheric pressure   [N/m2]
32
33   REAL(wp), ALLOCATABLE, SAVE, PUBLIC, DIMENSION(:,:) ::   ssh_ib    ! Inverse barometer now    sea surface height   [m]
34   REAL(wp), ALLOCATABLE, SAVE, PUBLIC, DIMENSION(:,:) ::   ssh_ibb   ! Inverse barometer before sea surface height   [m]
35   REAL(wp), ALLOCATABLE, SAVE, PUBLIC, DIMENSION(:,:) ::   apr       ! atmospheric pressure at kt                 [N/m2]
36   
37   REAL(wp) ::   tarea                ! whole domain mean masked ocean surface
38   REAL(wp) ::   r1_grau              ! = 1.e0 / (grav * rau0)
39   
40   TYPE(FLD), ALLOCATABLE, DIMENSION(:) ::   sf_apr   ! structure of input fields (file informations, fields read)
41
42   !!----------------------------------------------------------------------
43   !! NEMO/OCE 4.0 , NEMO Consortium (2018)
44   !! $Id$
45   !! Software governed by the CeCILL license (see ./LICENSE)
46   !!----------------------------------------------------------------------
47CONTAINS
48
49   SUBROUTINE sbc_apr_init
50      !!---------------------------------------------------------------------
51      !!                     ***  ROUTINE sbc_apr  ***
52      !!
53      !! ** Purpose :   read atmospheric pressure fields in netcdf files.
54      !!
55      !! ** Method  : - Read namelist namsbc_apr
56      !!              - Read Patm fields in netcdf files
57      !!              - Compute reference atmospheric pressure
58      !!              - Compute inverse barometer ssh
59      !! ** action  :   apr      : atmospheric pressure at kt
60      !!                ssh_ib   : inverse barometer ssh at kt
61      !!---------------------------------------------------------------------
62      INTEGER            ::   ierror  ! local integer
63      INTEGER            ::   ios     ! Local integer output status for namelist read
64      !!
65      CHARACTER(len=100) ::  cn_dir   ! Root directory for location of ssr files
66      TYPE(FLD_N)        ::  sn_apr   ! informations about the fields to be read
67      LOGICAL            ::  lrxios   ! read restart using XIOS?
68      !!
69      NAMELIST/namsbc_apr/ cn_dir, sn_apr, ln_ref_apr, rn_pref, ln_apr_obc
70      !!----------------------------------------------------------------------
71      READ  ( numnam_ref, namsbc_apr, IOSTAT = ios, ERR = 901)
72901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namsbc_apr in reference namelist' )
73
74      READ  ( numnam_cfg, namsbc_apr, IOSTAT = ios, ERR = 902 )
75902   IF( ios >  0 )   CALL ctl_nam ( ios , 'namsbc_apr in configuration namelist' )
76      IF(lwm) WRITE ( numond, namsbc_apr )
77      !
78      ALLOCATE( sf_apr(1), STAT=ierror )           !* allocate and fill sf_sst (forcing structure) with sn_sst
79      IF( ierror > 0 )   CALL ctl_stop( 'STOP', 'sbc_apr: unable to allocate sf_apr structure' )
80      !
81      CALL fld_fill( sf_apr, (/ sn_apr /), cn_dir, 'sbc_apr', 'Atmospheric pressure ', 'namsbc_apr' )
82                                ALLOCATE( sf_apr(1)%fnow(jpi,jpj,1)   )
83      IF( sn_apr%ln_tint )   ALLOCATE( sf_apr(1)%fdta(jpi,jpj,1,2) )
84                             ALLOCATE( ssh_ib(jpi,jpj) , ssh_ibb(jpi,jpj) )
85                             ALLOCATE( apr (jpi,jpj) )
86      !
87      IF( lwp )THEN                                 !* control print
88         WRITE(numout,*)
89         WRITE(numout,*) '   Namelist namsbc_apr : Atmospheric PRessure as extrenal forcing'
90         WRITE(numout,*) '      ref. pressure: global mean Patm (T) or a constant (F)  ln_ref_apr = ', ln_ref_apr
91      ENDIF
92      !
93      IF( ln_ref_apr ) THEN                        !* Compute whole inner domain mean masked ocean surface
94         tarea = glob_sum( 'sbcapr', e1e2t(:,:) )
95         IF(lwp) WRITE(numout,*) '         Variable ref. Patm computed over a ocean surface of ', tarea*1e-6, 'km2'
96      ELSE
97         IF(lwp) WRITE(numout,*) '         Reference Patm used : ', rn_pref, ' N/m2'
98      ENDIF
99      !
100      r1_grau = 1.e0 / (grav * rau0)               !* constant for optimization
101      !
102      !                                            !* control check
103      IF( ln_apr_obc  ) THEN
104         IF(lwp) WRITE(numout,*) '         Inverse barometer added to OBC ssh data'
105      ENDIF
106!jc: stop below should rather be a warning
107      IF( ln_apr_obc .AND. .NOT.ln_apr_dyn   )   &
108            CALL ctl_warn( 'sbc_apr: use inverse barometer ssh at open boundary ONLY requires ln_apr_dyn=T' )
109      !
110      IF( lwxios ) THEN
111         CALL iom_set_rstw_var_active('ssh_ibb')
112      ENDIF
113   END SUBROUTINE sbc_apr_init
114
115   SUBROUTINE sbc_apr( kt )
116      !!---------------------------------------------------------------------
117      !!                     ***  ROUTINE sbc_apr  ***
118      !!
119      !! ** Purpose :   read atmospheric pressure fields in netcdf files.
120      !!
121      !! ** Method  : - Read namelist namsbc_apr
122      !!              - Read Patm fields in netcdf files
123      !!              - Compute reference atmospheric pressure
124      !!              - Compute inverse barometer ssh
125      !! ** action  :   apr      : atmospheric pressure at kt
126      !!                ssh_ib   : inverse barometer ssh at kt
127      !!---------------------------------------------------------------------
128      INTEGER, INTENT(in)::   kt   ! ocean time step
129      !
130      !!----------------------------------------------------------------------
131
132      !                                         ! ========================== !
133      IF( MOD( kt-1, nn_fsbc ) == 0 ) THEN      !    At each sbc time-step   !
134         !                                      ! ===========+++============ !
135         !
136         IF( kt /= nit000 )   ssh_ibb(:,:) = ssh_ib(:,:)    !* Swap of ssh_ib fields
137         !
138         CALL fld_read( kt, nn_fsbc, sf_apr )               !* input Patm provided at kt + nn_fsbc/2
139         !
140         !                                                  !* update the reference atmospheric pressure (if necessary)
141         IF( ln_ref_apr )   rn_pref = glob_sum( 'sbcapr', sf_apr(1)%fnow(:,:,1) * e1e2t(:,:) ) / tarea
142         !
143         !                                                  !* Patm related forcing at kt
144         ssh_ib(:,:) = - ( sf_apr(1)%fnow(:,:,1) - rn_pref ) * r1_grau    ! equivalent ssh (inverse barometer)
145         apr   (:,:) =     sf_apr(1)%fnow(:,:,1)                        ! atmospheric pressure
146         !
147         CALL iom_put( "ssh_ib", ssh_ib )                   !* output the inverse barometer ssh
148      ENDIF
149
150      !                                         ! ---------------------------------------- !
151      IF( kt == nit000 ) THEN                   !   set the forcing field at nit000 - 1    !
152         !                                      ! ---------------------------------------- !
153         !                                            !* Restart: read in restart file
154         IF( ln_rstart .AND. iom_varid( numror, 'ssh_ibb', ldstop = .FALSE. ) > 0 ) THEN
155            IF(lwp) WRITE(numout,*) 'sbc_apr:   ssh_ibb read in the restart file'
156            CALL iom_get( numror, jpdom_autoglo, 'ssh_ibb', ssh_ibb, ldxios = lrxios )   ! before inv. barometer ssh
157            !
158         ELSE                                         !* no restart: set from nit000 values
159            IF(lwp) WRITE(numout,*) 'sbc_apr:   ssh_ibb set to nit000 values'
160            ssh_ibb(:,:) = ssh_ib(:,:)
161         ENDIF
162      ENDIF
163      !                                         ! ---------------------------------------- !
164      IF( lrst_oce ) THEN                       !      Write in the ocean restart file     !
165         !                                      ! ---------------------------------------- !
166         IF(lwp) WRITE(numout,*)
167         IF(lwp) WRITE(numout,*) 'sbc_apr : ssh_ib written in ocean restart file at it= ', kt,' date= ', ndastp
168         IF(lwp) WRITE(numout,*) '~~~~'
169         IF( lwxios ) CALL iom_swap(      cwxios_context          )
170         CALL iom_rstput( kt, nitrst, numrow, 'ssh_ibb' , ssh_ib, ldxios = lwxios )
171         IF( lwxios ) CALL iom_swap(      cxios_context          )
172      ENDIF
173      !
174   END SUBROUTINE sbc_apr
175     
176   !!======================================================================
177END MODULE sbcapr
Note: See TracBrowser for help on using the repository browser.