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.
sbcflx_adj.F90 in branches/UKMO/dev_r5518_flux_adjust/NEMOGCM/NEMO/OPA_SRC/SBC – NEMO

source: branches/UKMO/dev_r5518_flux_adjust/NEMOGCM/NEMO/OPA_SRC/SBC/sbcflx_adj.F90 @ 6773

Last change on this file since 6773 was 6773, checked in by kuniko, 8 years ago

Recommented out lines for FA test and added "&" at end of continuation line 125

File size: 14.2 KB
Line 
1MODULE sbcflx_adj
2   !!======================================================================
3   !!                       ***  MODULE  sbcflx_adj  ***
4   !! Surface module :  flux adjustment of heat/freshwater. Add qrp/erp obtained from sbcssr
5   !!======================================================================
6   !! History :  0.0  !  2015-10-14  (K. Yamazaki)  Original code
7   !!----------------------------------------------------------------------
8
9   !!----------------------------------------------------------------------
10   !!   sbc_flx_adj       : add qrp/erp to sbc to perform flux adjustment
11   !!   sbc_flx_adj_init  : initialisation of flux adjustment
12   !!----------------------------------------------------------------------
13   USE oce            ! ocean dynamics and tracers
14   USE dom_oce        ! ocean space and time domain
15   USE sbc_oce        ! surface boundary condition
16   USE phycst         ! physical constants
17   USE sbcrnf         ! surface boundary condition : runoffs
18   !
19   USE fldread        ! read input fields
20   USE iom            ! I/O manager
21   USE in_out_manager ! I/O manager
22   USE lib_mpp        ! distribued memory computing library
23   USE lbclnk         ! ocean lateral boundary conditions (or mpp link)
24   USE timing         ! Timing
25   USE lib_fortran    ! Fortran utilities (allows no signed zero when 'key_nosignedzero' defined) 
26
27   IMPLICIT NONE
28   PRIVATE
29
30   PUBLIC   sbc_flx_adj        ! routine called in sbcmod
31   PUBLIC   sbc_flx_adj_init   ! routine called in sbcmod
32
33   !ky 11/12/2015 recommented below two lines
34   !!ky 3/12/2015 uncommented below two lines for FA test!
35   !!ky 20/06/2016 uncommented lower line of below two lines for FA test!
36   !!ky 01/07/2016 recommented lower line of below two lines
37   !REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   erp   !: evaporation damping   [kg/m2/s]
38   !REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   qrp   !: heat flux damping        [w/m2]
39
40   !                                   !!* Namelist namsbc_flx_adj *
41   INTEGER, PUBLIC ::   nn_flxadjht     ! Heat/freshwater flux adjustment indicator
42   INTEGER, PUBLIC ::   nn_flxadjfw     ! Heat/freshwater flux adjustment indicator
43   LOGICAL         ::   ln_sssr_bnd     ! flag to bound erp term
44   REAL(wp)        ::   rn_sssr_bnd     ! ABS(Max./Min.) value of erp term [mm/day]
45
46   REAL(wp) , ALLOCATABLE, DIMENSION(:) ::   buffer   ! Temporary buffer for exchange
47   TYPE(FLD), ALLOCATABLE, DIMENSION(:) ::   sf_erp   ! structure of input erp (file informations, fields read)
48   TYPE(FLD), ALLOCATABLE, DIMENSION(:) ::   sf_qrp   ! structure of input qrp (file informations, fields read)
49
50   !! * Substitutions
51#  include "domzgr_substitute.h90"
52   !!----------------------------------------------------------------------
53   !! NEMO/OPA 4.0 , NEMO Consortium (2011)
54   !! $Id: sbcssr.F90 4990 2014-12-15 16:42:49Z timgraham $
55   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
56   !!----------------------------------------------------------------------
57CONTAINS
58
59   SUBROUTINE sbc_flx_adj( kt )
60      !!---------------------------------------------------------------------
61      !!                     ***  ROUTINE sbc_flx_adj  ***
62      !!
63      !! ** Purpose :   Add to heat and/or freshwater fluxes a qrp and/or erp
64      !!                to flux adjust temperature/salinity
65      !!
66      !! ** Method  : - Read namelist namsbc_flx_adj
67      !!              - Read calculated qrp and/or erp
68      !!              - at each nscb time step
69      !!                   add qrp on qns    (nn_flxadjht = 1)
70      !!                   add erp on sfx        (nn_flxadjfw = 1)
71      !!                   add erp on emp        (nn_flxadjfw = 2)
72      !!---------------------------------------------------------------------
73      INTEGER, INTENT(in   ) ::   kt   ! ocean time step
74      !!
75      INTEGER  ::   ji, jj   ! dummy loop indices
76      REAL(wp) ::   zerp     ! local scalar for evaporation damping
77      REAL(wp) ::   zqrp     ! local scalar for heat flux damping
78      REAL(wp) ::   zerp_bnd ! local scalar for unit conversion of rn_epr_max factor
79      INTEGER  ::   ierror   ! return error code
80      !!
81      CHARACTER(len=100) ::  cn_dir          ! Root directory for location of ssr files
82      TYPE(FLD_N) ::   sn_qrp, sn_erp        ! informations about the fields to be read
83      !!----------------------------------------------------------------------
84      !
85      !!write(numout,*) '*** In sbcflx_adj ***'
86
87      IF( nn_timing == 1 )  CALL timing_start('sbc_flx_adj')
88      !
89      IF( nn_flxadjht + nn_flxadjfw /= 0 ) THEN
90         !
91         IF( nn_flxadjht == 1)   CALL fld_read( kt, nn_fsbc, sf_qrp )   ! Read qrp data and provides it at kt
92         IF( nn_flxadjfw >= 1)   CALL fld_read( kt, nn_fsbc, sf_erp )   ! Read erp data and provides it at kt
93         !
94         !                                         ! ========================= !
95         IF( MOD( kt-1, nn_fsbc ) == 0 ) THEN      !    Add restoring term     !
96            !                                      ! ========================= !
97            !
98            IF( nn_flxadjht == 1 ) THEN                                   !* Anomalous heat flux term (qrp)
99               DO jj = 1, jpj
100                  DO ji = 1, jpi
101                     zqrp = sf_qrp(1)%fnow(ji,jj,1)
102                     !ky 11/12/2015 commented out 1 line below
103                     !!ky 3/12/2015 1 line below for FA test!
104                     !!ky 20/06/2016 uncommented 1 line below for FA test!
105                     !!ky 01/07/2016 recommented 1 line below
106                     !qrp(ji,jj) = sf_qrp(1)%fnow(ji,jj,1)
107                     qns(ji,jj) = qns(ji,jj) + zqrp
108                  END DO
109               END DO
110               !ky 11/12/2015 recommented out below 1 line below
111               !!ky 3/12/2015 uncommented below 1 line below for FA test!
112               !!ky 20/06/2016 uncommented 1 line below for FA test!
113               !!ky 01/06/2016 recommented 1 line below
114               !CALL iom_put( "qrp", qrp )                             ! heat flux damping
115            ENDIF
116            !
117            IF( nn_flxadjfw == 1 ) THEN                               !* Anomalous freshwater term !(salt flux only (sfx))
118!CDIR COLLAPSE
119               DO jj = 1, jpj
120                  !!write(numout,*) 'sf_qrp(1)%fnow(30,',jj,',1)=',sf_qrp(1)%fnow(30,jj,1), &
121                  !!  &            'sf_erp(1)%fnow(30,',jj,',1)=',sf_erp(1)%fnow(30,jj,1), &
122                  !!  &            'sst_m(30,',jj,')=',sst_m(30,jj),'sss_m(30,',jj,')=',sss_m(30,jj)
123                  DO ji = 1, jpi
124                     zerp = ( 1. - 2.*rnfmsk(ji,jj) )  &              ! No damping in vicinity of river mouths
125                        &        * sf_erp(1)%fnow(ji,jj,1)  &
126                        &        * MAX( sss_m(ji,jj), 1.e-20 )! reconverted into salinity flux
127                     !ky 16/06/2016 restored above line (multiplication by MAX...)
128                     !ky 11/12/2015 recommented out 1 line below
129                     !!ky 3/12/2015 1 line below for FA test!
130                     !erp(ji,jj) = sf_erp(1)%fnow(ji,jj,1)
131                     sfx(ji,jj) = sfx(ji,jj) + zerp                 ! salt flux
132                  END DO
133               END DO
134               !ky 11/12/2015 recommented out below one line
135               !!ky 3/12/2015 uncommented below one line for FA test!
136               !CALL iom_put( "erp", erp )                             ! freshwater flux damping
137               !
138            ELSEIF( nn_flxadjfw == 2 ) THEN                               !* Salinity damping term (volume flux (emp) and associated heat flux (qns)
139               zerp_bnd = rn_sssr_bnd / rday                          !       -              -   
140!CDIR COLLAPSE
141               DO jj = 1, jpj
142                  DO ji = 1, jpi                           
143                     zerp = ( 1. - 2.*rnfmsk(ji,jj) )  &              ! No damping in vicinity of river mouths
144                        &        * sf_erp(1)%fnow(ji,jj,1)
145                     IF( ln_sssr_bnd )   zerp = SIGN( 1., zerp ) * MIN( zerp_bnd, ABS(zerp) )
146                     !ky 11/12/2015 recommented out 1 line below
147                     !!ky 3/12/2015 1 line below for FA test!
148                     !erp(ji,jj) = sf_erp(1)%fnow(ji,jj,1)
149                     emp(ji,jj) = emp (ji,jj) + zerp
150                     qns(ji,jj) = qns(ji,jj) - zerp * rcp * sst_m(ji,jj)
151                  END DO
152               END DO
153               !ky 11/12/2015 recommented out below 1 line
154               !!ky 3/12/2015 uncommented below 1 line for FA test!
155               !CALL iom_put( "erp", erp )                             ! freshwater flux damping
156            ENDIF
157            !
158         ENDIF
159         !
160      ENDIF
161      !
162      IF( nn_timing == 1 )  CALL timing_stop('sbc_flx_adj')
163      !
164   END SUBROUTINE sbc_flx_adj
165
166 
167   SUBROUTINE sbc_flx_adj_init
168      !!---------------------------------------------------------------------
169      !!                  ***  ROUTINE sbc_flx_adj_init  ***
170      !!
171      !! ** Purpose :   initialisation of surface damping term
172      !!
173      !! ** Method  : - Read namelist namsbc_flx_adj
174      !ky!!!              - Read observed SST and/or SSS if required
175      !!---------------------------------------------------------------------
176      INTEGER  ::   ji, jj   ! dummy loop indices
177      REAL(wp) ::   zerp     ! local scalar for evaporation damping
178      REAL(wp) ::   zqrp     ! local scalar for heat flux damping
179      REAL(wp) ::   zerp_bnd ! local scalar for unit conversion of rn_epr_max factor
180      INTEGER  ::   ierror   ! return error code
181      !!
182      CHARACTER(len=100) ::  cn_dir          ! Root directory for location of ssr files
183      TYPE(FLD_N) ::   sn_qrp, sn_erp        ! informations about the fields to be read
184      NAMELIST/namsbc_flx_adj/ cn_dir, nn_flxadjht, nn_flxadjfw, sn_qrp, sn_erp,   &
185         &                     ln_sssr_bnd, rn_sssr_bnd
186      INTEGER     ::  ios
187      !!----------------------------------------------------------------------
188      !
189 
190      !!write(numout,*) '*** in sbcflx_adj_init ***'
191
192      REWIND( numnam_ref )              ! Namelist namsbc_flx_adj in reference namelist :
193      READ  ( numnam_ref, namsbc_flx_adj, IOSTAT = ios, ERR = 901)
194901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namsbc_flx_adj in reference namelist', lwp )
195
196      REWIND( numnam_cfg )              ! Namelist namsbc_flx_adj in configuration namelist :
197      READ  ( numnam_cfg, namsbc_flx_adj, IOSTAT = ios, ERR = 902 )
198902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namsbc_flx_adj in configuration namelist', lwp )
199      IF(lwm) WRITE ( numond, namsbc_flx_adj )
200
201      IF(lwp) THEN                 !* control print
202         WRITE(numout,*)
203         WRITE(numout,*) 'sbc_flx_adj : Heat and/or freshwater flux adjustment term '
204         WRITE(numout,*) '~~~~~~~ '
205         WRITE(numout,*) '   Namelist namsbc_flx_adj :'
206         WRITE(numout,*) '      Anom. heat flux (qrp) term (Yes=1)             nn_flxadjht     = ', nn_flxadjht
207         WRITE(numout,*) '      Anom. fw flux (erp) term (Yes=1, salt flux)    nn_flxadjfw     = ', nn_flxadjfw
208         WRITE(numout,*) '                                           (Yes=2, volume flux) '
209         WRITE(numout,*) '      flag to bound erp term                 ln_sssr_bnd = ', ln_sssr_bnd
210         WRITE(numout,*) '      ABS(Max./Min.) erp threshold           rn_sssr_bnd = ', rn_sssr_bnd, ' mm/day'
211      ENDIF
212      !
213      !                            !* Allocate erp and qrp array
214      !ky 11/12/2015 recommented out below two lines
215      !!ky 3/12/2015 uncommented below two lines for FA test!
216      !ALLOCATE( qrp(jpi,jpj), erp(jpi,jpj), STAT=ierror )
217      !IF( ierror > 0 )   CALL ctl_stop( 'STOP', 'sbc_ssr: unable to allocate erp and qrp array' )
218      !!ky 20/06/2016 uncommented below two lines for FA test!
219      !!ky 01/07/2016 recommented below two lines
220      !ALLOCATE( qrp(jpi,jpj), STAT=ierror )
221      !IF( ierror > 0 )   CALL ctl_stop( 'STOP', 'sbcflx_adj: unable to allocate qrp array' )
222      !
223      IF( nn_flxadjht == 1 ) THEN      !* set sf_qrp structure & allocate arrays
224         !
225         ALLOCATE( sf_qrp(1), STAT=ierror )
226         IF( ierror > 0 )   CALL ctl_stop( 'STOP', 'sbc_flx_adj: unable to allocate sf_qrp structure' )
227         ALLOCATE( sf_qrp(1)%fnow(jpi,jpj,1), STAT=ierror )
228         IF( ierror > 0 )   CALL ctl_stop( 'STOP', 'sbc_flx_adj: unable to allocate sf_qrp now array' )
229         !
230         ! fill sf_qrp with sn_qrp and control print
231         CALL fld_fill( sf_qrp, (/ sn_qrp /), cn_dir, 'sbc_qrp', 'Heat flux adjustment', 'namsbc_flx_adj' )
232         IF( sf_qrp(1)%ln_tint )   ALLOCATE( sf_qrp(1)%fdta(jpi,jpj,1,2), STAT=ierror )
233         IF( ierror > 0 )   CALL ctl_stop( 'STOP', 'sbc_flx_adj: unable to allocate sf_qrp data array' )
234         !
235      ENDIF
236      !
237      IF( nn_flxadjfw >= 1 ) THEN      !* set sf_erp structure & allocate arrays
238         !
239         ALLOCATE( sf_erp(1), STAT=ierror )
240         IF( ierror > 0 )   CALL ctl_stop( 'STOP', 'sbc_flx_adj: unable to allocate sf_erp structure' )
241         ALLOCATE( sf_erp(1)%fnow(jpi,jpj,1), STAT=ierror )
242         IF( ierror > 0 )   CALL ctl_stop( 'STOP', 'sbc_flx_adj: unable to allocate sf_erp now array' )
243         !
244         ! fill sf_erp with sn_erp and control print
245         CALL fld_fill( sf_erp, (/ sn_erp /), cn_dir, 'sbc_erp', 'Freshwater flux adjustment term', 'namsbc_flx_adj' )
246         IF( sf_erp(1)%ln_tint )   ALLOCATE( sf_erp(1)%fdta(jpi,jpj,1,2), STAT=ierror )
247         IF( ierror > 0 )   CALL ctl_stop( 'STOP', 'sbc_flx_adj: unable to allocate sf_erp data array' )
248         !
249      ENDIF
250      !
251      !ky!!                            !* Initialize qrp and erp if no restoring
252      !ky 11/12/2015 commented out below two lines
253      !!ky 3/12/2015 below two lines for FA test!
254      !!ky 20/06/2016 uncommented below line for FA test!
255      !!ky 01/07/2016 recommented below line
256      !IF( nn_flxadjht /= 1                   )   qrp(:,:) = 0._wp
257      !IF( nn_flxadjfw /= 1 .OR. nn_flxadjfw /= 2 )   erp(:,:) = 0._wp
258      !!ky!!IF( nn_sstr /= 1                   )   qrp(:,:) = 0._wp
259      !!ky!!IF( nn_sssr /= 1 .OR. nn_sssr /= 2 )   erp(:,:) = 0._wp
260      !
261   END SUBROUTINE sbc_flx_adj_init
262     
263   !!======================================================================
264END MODULE sbcflx_adj
Note: See TracBrowser for help on using the repository browser.