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 | !!---------------------------------------------------------------------- |
---|
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 | !!---------------------------------------------------------------------- |
---|
47 | CONTAINS |
---|
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 | REWIND( numnam_ref ) ! Namelist namsbc_apr in reference namelist : File for atmospheric pressure forcing |
---|
72 | READ ( numnam_ref, namsbc_apr, IOSTAT = ios, ERR = 901) |
---|
73 | 901 IF( ios /= 0 ) CALL ctl_nam ( ios , 'namsbc_apr in reference namelist', lwp ) |
---|
74 | |
---|
75 | REWIND( numnam_cfg ) ! Namelist namsbc_apr in configuration namelist : File for atmospheric pressure forcing |
---|
76 | READ ( numnam_cfg, namsbc_apr, IOSTAT = ios, ERR = 902 ) |
---|
77 | 902 IF( ios > 0 ) CALL ctl_nam ( ios , 'namsbc_apr in configuration namelist', lwp ) |
---|
78 | IF(lwm) WRITE ( numond, namsbc_apr ) |
---|
79 | ! |
---|
80 | ALLOCATE( sf_apr(1), STAT=ierror ) !* allocate and fill sf_sst (forcing structure) with sn_sst |
---|
81 | IF( ierror > 0 ) CALL ctl_stop( 'STOP', 'sbc_apr: unable to allocate sf_apr structure' ) |
---|
82 | ! |
---|
83 | CALL fld_fill( sf_apr, (/ sn_apr /), cn_dir, 'sbc_apr', 'Atmospheric pressure ', 'namsbc_apr' ) |
---|
84 | ALLOCATE( sf_apr(1)%fnow(jpi,jpj,1) ) |
---|
85 | IF( sn_apr%ln_tint ) ALLOCATE( sf_apr(1)%fdta(jpi,jpj,1,2) ) |
---|
86 | ALLOCATE( ssh_ib(jpi,jpj) , ssh_ibb(jpi,jpj) ) |
---|
87 | ALLOCATE( apr (jpi,jpj) ) |
---|
88 | ! |
---|
89 | IF( lwp )THEN !* control print |
---|
90 | WRITE(numout,*) |
---|
91 | WRITE(numout,*) ' Namelist namsbc_apr : Atmospheric PRessure as extrenal forcing' |
---|
92 | WRITE(numout,*) ' ref. pressure: global mean Patm (T) or a constant (F) ln_ref_apr = ', ln_ref_apr |
---|
93 | ENDIF |
---|
94 | ! |
---|
95 | IF( ln_ref_apr ) THEN !* Compute whole inner domain mean masked ocean surface |
---|
96 | tarea = glob_sum( 'sbcapr', e1e2t(:,:) ) |
---|
97 | IF(lwp) WRITE(numout,*) ' Variable ref. Patm computed over a ocean surface of ', tarea*1e-6, 'km2' |
---|
98 | ELSE |
---|
99 | IF(lwp) WRITE(numout,*) ' Reference Patm used : ', rn_pref, ' N/m2' |
---|
100 | ENDIF |
---|
101 | ! |
---|
102 | r1_grau = 1.e0 / (grav * rau0) !* constant for optimization |
---|
103 | ! |
---|
104 | ! !* control check |
---|
105 | IF ( ln_apr_obc ) THEN |
---|
106 | IF(lwp) WRITE(numout,*) ' Inverse barometer added to OBC ssh data' |
---|
107 | ENDIF |
---|
108 | !jc: stop below should rather be a warning |
---|
109 | IF( ln_apr_obc .AND. .NOT.ln_apr_dyn ) & |
---|
110 | CALL ctl_warn( 'sbc_apr: use inverse barometer ssh at open boundary ONLY requires ln_apr_dyn=T' ) |
---|
111 | ! |
---|
112 | IF( lwxios ) THEN |
---|
113 | CALL iom_set_rstw_var_active('ssh_ibb') |
---|
114 | ENDIF |
---|
115 | END SUBROUTINE sbc_apr_init |
---|
116 | |
---|
117 | SUBROUTINE sbc_apr( kt ) |
---|
118 | !!--------------------------------------------------------------------- |
---|
119 | !! *** ROUTINE sbc_apr *** |
---|
120 | !! |
---|
121 | !! ** Purpose : read atmospheric pressure fields in netcdf files. |
---|
122 | !! |
---|
123 | !! ** Method : - Read namelist namsbc_apr |
---|
124 | !! - Read Patm fields in netcdf files |
---|
125 | !! - Compute reference atmospheric pressure |
---|
126 | !! - Compute inverse barometer ssh |
---|
127 | !! ** action : apr : atmospheric pressure at kt |
---|
128 | !! ssh_ib : inverse barometer ssh at kt |
---|
129 | !!--------------------------------------------------------------------- |
---|
130 | INTEGER, INTENT(in):: kt ! ocean time step |
---|
131 | ! |
---|
132 | !!---------------------------------------------------------------------- |
---|
133 | |
---|
134 | ! ! ========================== ! |
---|
135 | IF( MOD( kt-1, nn_fsbc ) == 0 ) THEN ! At each sbc time-step ! |
---|
136 | ! ! ===========+++============ ! |
---|
137 | ! |
---|
138 | IF( kt /= nit000 ) ssh_ibb(:,:) = ssh_ib(:,:) !* Swap of ssh_ib fields |
---|
139 | ! |
---|
140 | CALL fld_read( kt, nn_fsbc, sf_apr ) !* input Patm provided at kt + nn_fsbc/2 |
---|
141 | ! |
---|
142 | ! !* update the reference atmospheric pressure (if necessary) |
---|
143 | IF( ln_ref_apr ) rn_pref = glob_sum( 'sbcapr', sf_apr(1)%fnow(:,:,1) * e1e2t(:,:) ) / tarea |
---|
144 | ! |
---|
145 | ! !* Patm related forcing at kt |
---|
146 | ssh_ib(:,:) = - ( sf_apr(1)%fnow(:,:,1) - rn_pref ) * r1_grau ! equivalent ssh (inverse barometer) |
---|
147 | apr (:,:) = sf_apr(1)%fnow(:,:,1) ! atmospheric pressure |
---|
148 | ! |
---|
149 | CALL iom_put( "ssh_ib", ssh_ib ) !* output the inverse barometer ssh |
---|
150 | ENDIF |
---|
151 | |
---|
152 | ! ! ---------------------------------------- ! |
---|
153 | IF( kt == nit000 ) THEN ! set the forcing field at nit000 - 1 ! |
---|
154 | ! ! ---------------------------------------- ! |
---|
155 | ! !* Restart: read in restart file |
---|
156 | IF( ln_rstart .AND. iom_varid( numror, 'ssh_ibb', ldstop = .FALSE. ) > 0 ) THEN |
---|
157 | IF(lwp) WRITE(numout,*) 'sbc_apr: ssh_ibb read in the restart file' |
---|
158 | CALL iom_get( numror, jpdom_autoglo, 'ssh_ibb', ssh_ibb, ldxios = lrxios ) ! before inv. barometer ssh |
---|
159 | ! |
---|
160 | ELSE !* no restart: set from nit000 values |
---|
161 | IF(lwp) WRITE(numout,*) 'sbc_apr: ssh_ibb set to nit000 values' |
---|
162 | ssh_ibb(:,:) = ssh_ib(:,:) |
---|
163 | ENDIF |
---|
164 | ENDIF |
---|
165 | ! ! ---------------------------------------- ! |
---|
166 | IF( lrst_oce ) THEN ! Write in the ocean restart file ! |
---|
167 | ! ! ---------------------------------------- ! |
---|
168 | IF(lwp) WRITE(numout,*) |
---|
169 | IF(lwp) WRITE(numout,*) 'sbc_apr : ssh_ib written in ocean restart file at it= ', kt,' date= ', ndastp |
---|
170 | IF(lwp) WRITE(numout,*) '~~~~' |
---|
171 | IF( lwxios ) CALL iom_swap( cwxios_context ) |
---|
172 | CALL iom_rstput( kt, nitrst, numrow, 'ssh_ibb' , ssh_ib, ldxios = lwxios ) |
---|
173 | IF( lwxios ) CALL iom_swap( cxios_context ) |
---|
174 | ENDIF |
---|
175 | ! |
---|
176 | END SUBROUTINE sbc_apr |
---|
177 | |
---|
178 | !!====================================================================== |
---|
179 | END MODULE sbcapr |
---|