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

source: branches/UKMO/r6232_HZG_WAVE-coupling/NEMOGCM/NEMO/OPA_SRC/SBC/sbcflx.F90 @ 8756

Last change on this file since 8756 was 8756, checked in by jcastill, 6 years ago

Changes for receiving the ocean wind stress components from a wave model, both in forced and coupled mode
WARNING: this might not work properly without merging the branch svn+ssh://forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/branches/UKMO/AMM15_v3_6_STABLE_package_UKEP

File size: 14.6 KB
Line 
1MODULE sbcflx
2   !!======================================================================
3   !!                       ***  MODULE  sbcflx  ***
4   !! Ocean forcing:  momentum, heat and freshwater flux formulation
5   !!=====================================================================
6   !! History :  1.0  !  2006-06  (G. Madec)  Original code
7   !!            3.3  !  2010-10  (S. Masson)  add diurnal cycle
8   !!----------------------------------------------------------------------
9
10   !!----------------------------------------------------------------------
11   !!   namflx   : flux formulation namlist
12   !!   sbc_flx  : flux formulation as ocean surface boundary condition (forced mode, fluxes read in NetCDF files)
13   !!----------------------------------------------------------------------
14   USE oce             ! ocean dynamics and tracers
15   USE dom_oce         ! ocean space and time domain
16   USE sbc_oce         ! surface boundary condition: ocean fields
17   USE sbcdcy          ! surface boundary condition: diurnal cycle on qsr
18   USE phycst          ! physical constants
19   USE fldread         ! read input fields
20   USE iom             ! IOM library
21   USE in_out_manager  ! I/O manager
22   USE sbcwave         ! wave physics
23   USE lib_mpp         ! distribued memory computing library
24   USE lbclnk          ! ocean lateral boundary conditions (or mpp link)
25   USE wrk_nemo        ! work arrays
26
27   IMPLICIT NONE
28   PRIVATE
29
30   PUBLIC sbc_flx       ! routine called by step.F90
31
32   INTEGER             ::   jpfld   = 6   ! maximum number of files to read
33   INTEGER             ::   jp_utau       ! index of wind stress (i-component) file
34   INTEGER             ::   jp_vtau       ! index of wind stress (j-component) file
35   INTEGER             ::   jp_qtot       ! index of total (non solar+solar) heat file
36   INTEGER             ::   jp_qsr        ! index of solar heat file
37   INTEGER             ::   jp_emp        ! index of evaporation-precipation file
38   INTEGER             ::   jp_press      ! index of pressure for UKMO shelf fluxes
39   TYPE(FLD), ALLOCATABLE, DIMENSION(:) ::   sf    ! structure of input fields (file informations, fields read)
40   LOGICAL , PUBLIC    ::   ln_shelf_flx = .FALSE. ! UKMO SHELF specific flux flag
41   LOGICAL , PUBLIC    ::   ln_rel_wind = .FALSE.  ! UKMO SHELF specific flux flag - relative winds
42   REAL(wp)            ::   rn_wfac                ! multiplication factor for ice/ocean velocity in the calculation of wind stress (clem)
43   INTEGER             ::   jpfld_local   ! maximum number of files to read (locally modified depending on ln_shelf_flx)
44
45   !! * Substitutions
46#  include "domzgr_substitute.h90"
47#  include "vectopt_loop_substitute.h90"
48   !!----------------------------------------------------------------------
49   !! NEMO/OPA 3.3 , NEMO-consortium (2010)
50   !! $Id$
51   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
52   !!----------------------------------------------------------------------
53CONTAINS
54
55   SUBROUTINE sbc_flx( kt )
56      !!---------------------------------------------------------------------
57      !!                    ***  ROUTINE sbc_flx  ***
58      !!                   
59      !! ** Purpose :   provide at each time step the surface ocean fluxes
60      !!                (momentum, heat, freshwater and runoff)
61      !!
62      !! ** Method  : - READ each fluxes in NetCDF files:
63      !!                   i-component of the stress              utau  (N/m2)
64      !!                   j-component of the stress              vtau  (N/m2)
65      !!                   net downward heat flux                 qtot  (watt/m2)
66      !!                   net downward radiative flux            qsr   (watt/m2)
67      !!                   net upward freshwater (evapo - precip) emp   (kg/m2/s)
68      !!
69      !!      CAUTION :  - never mask the surface stress fields
70      !!                 - the stress is assumed to be in the (i,j) mesh referential
71      !!
72      !! ** Action  :   update at each time-step
73      !!              - utau, vtau  i- and j-component of the wind stress
74      !!              - taum        wind stress module at T-point
75      !!              - wndm        10m wind module at T-point
76      !!              - qns         non solar heat flux including heat flux due to emp
77      !!              - qsr         solar heat flux
78      !!              - emp         upward mass flux (evap. - precip.)
79      !!              - sfx         salt flux; set to zero at nit000 but possibly non-zero
80      !!                            if ice is present (computed in limsbc(_2).F90)
81      !!----------------------------------------------------------------------
82      INTEGER, INTENT(in) ::   kt   ! ocean time step
83      !!
84      INTEGER  ::   ji, jj, jf            ! dummy indices
85      INTEGER  ::   ierror                ! return error code
86      INTEGER  ::   ios                   ! Local integer output status for namelist read
87      REAL(wp) ::   zfact                 ! temporary scalar
88      REAL(wp) ::   zrhoa  = 1.22         ! Air density kg/m3
89      REAL(wp) ::   zcdrag = 1.5e-3       ! drag coefficient
90      REAL(wp) ::   totwind               ! UKMO SHELF: Module of wind speed
91      REAL(wp) ::   ztx, zty, zmod, zcoef ! temporary variables
92      !!
93      CHARACTER(len=100) ::  cn_dir                               ! Root directory for location of flx files
94      NAMELIST/namsbc_flx/ ln_shelf_flx, ln_rel_wind, rn_wfac     ! Put here to allow merging with another UKMO branch
95      LOGICAL  :: ln_readtau                                      ! Is it necessary to read tau from file?
96      TYPE(FLD_N), DIMENSION(jpfld) ::   slf_i                    ! array of namelist information structures
97      TYPE(FLD_N) ::   sn_utau, sn_vtau, sn_qtot, sn_qsr, sn_emp  ! informations about the fields to be read
98      NAMELIST/namsbc_flx/ cn_dir, sn_utau, sn_vtau, sn_qtot, sn_qsr, sn_emp
99      !!---------------------------------------------------------------------
100      !
101      ln_readtau = .NOT. (ln_wave .AND. ln_tauw )
102
103      ! prepare the index of the fields that have to be read
104      jpfld = 0
105      IF( ln_readtau ) THEN
106         jp_utau = jpfld+1
107         jp_vtau = jpfld+2
108         jpfld = jpfld+2
109      ELSE
110         jp_utau = 0   ;  jp_vtau = 0
111      ENDIF
112      jp_qtot = jpfld+1
113      jp_qsr = jpfld+2
114      jp_emp = jpfld+3
115      jp_press = jpfld+4
116      jpfld = jpfld+4
117
118      IF( kt == nit000 ) THEN                ! First call kt=nit000 
119         ! set file information
120         REWIND( numnam_ref )              ! Namelist namsbc_flx in reference namelist : Files for fluxes
121         READ  ( numnam_ref, namsbc_flx, IOSTAT = ios, ERR = 901)
122901      IF( ios /= 0 ) CALL ctl_nam ( ios , 'namsbc_flx in reference namelist', lwp )
123
124         REWIND( numnam_cfg )              ! Namelist namsbc_flx in configuration namelist : Files for fluxes
125         READ  ( numnam_cfg, namsbc_flx, IOSTAT = ios, ERR = 902 )
126902      IF( ios /= 0 ) CALL ctl_nam ( ios , 'namsbc_flx in configuration namelist', lwp )
127         IF(lwm) WRITE ( numond, namsbc_flx ) 
128         !
129         IF(lwp) THEN                        ! Namelist print
130            WRITE(numout,*)
131            WRITE(numout,*) 'sbc_flx : Flux forcing'
132            WRITE(numout,*) '~~~~~~~~~~~'
133            WRITE(numout,*) '       Namelist namsbc_flx : shelf seas configuration (force with winds instead of momentum)'
134            WRITE(numout,*) '          shelf seas configuration    ln_shelf_flx    = ', ln_shelf_flx
135            WRITE(numout,*) '          relative wind speed         ln_rel_wind     = ', ln_rel_wind
136            WRITE(numout,*) '          wind multiplication factor  rn_wfac         = ', rn_wfac
137         ENDIF
138         !                                         ! check: do we plan to use ln_dm2dc with non-daily forcing?
139         IF( ln_dm2dc .AND. sn_qsr%nfreqh /= 24 )   &
140            &   CALL ctl_stop( 'sbc_blk_core: ln_dm2dc can be activated only with daily short-wave forcing' ) 
141         !
142         !                                         ! store namelist information in an array
143         IF( ln_readtau ) THEN
144         slf_i(jp_utau) = sn_utau   ;   slf_i(jp_vtau) = sn_vtau
145         ENDIF
146         slf_i(jp_qtot) = sn_qtot   ;   slf_i(jp_qsr ) = sn_qsr 
147         slf_i(jp_emp ) = sn_emp
148         !
149         ALLOCATE( sf(jpfld), STAT=ierror )        ! set sf structure
150         IF( ierror > 0 ) THEN   
151            CALL ctl_stop( 'sbc_flx: unable to allocate sf structure' )   ;   RETURN 
152         ENDIF
153         DO ji= 1, jpfld
154            ALLOCATE( sf(ji)%fnow(jpi,jpj,1) )
155            IF( slf_i(ji)%ln_tint ) ALLOCATE( sf(ji)%fdta(jpi,jpj,1,2) )
156         END DO
157         !                                         ! fill sf with slf_i and control print
158         CALL fld_fill( sf, slf_i, cn_dir, 'sbc_flx', 'flux formulation for ocean surface boundary condition', 'namsbc_flx' )
159         !
160         sfx(:,:) = 0.0_wp                         ! salt flux due to freezing/melting (non-zero only if ice is present; set in limsbc(_2).F90)
161         !
162      ENDIF
163
164      CALL fld_read( kt, nn_fsbc, sf )                            ! input fields provided at the current time-step
165     
166      IF( MOD( kt-1, nn_fsbc ) == 0 ) THEN                        ! update ocean fluxes at each SBC frequency
167
168         !!UKMO SHELF wind speed relative to surface currents - put here to allow merging with coupling branch
169         IF( ln_shelf_flx .AND. ln_readtau ) THEN
170            CALL wrk_alloc( jpi,jpj, zwnd_i, zwnd_j )
171
172            IF( ln_rel_wind ) THEN
173               DO jj = 2, jpjm1
174                  DO ji = fs_2, fs_jpim1   ! vect. opt.
175                     zwnd_i(ji,jj) = ( sf(jp_utau)%fnow(ji,jj,1) - rn_wfac * 0.5 * ( ssu_m(ji-1,jj  ) + ssu_m(ji,jj) ))
176                     zwnd_j(ji,jj) = ( sf(jp_vtau)%fnow(ji,jj,1) - rn_wfac * 0.5 * ( ssv_m(ji  ,jj-1) + ssv_m(ji,jj) ))
177                  END DO
178               END DO
179               CALL lbc_lnk( zwnd_i(:,:) , 'T', -1. )
180               CALL lbc_lnk( zwnd_j(:,:) , 'T', -1. )
181            ELSE
182               zwnd_i(:,:) = sf(jp_utau)%fnow(:,:,1)
183               zwnd_j(:,:) = sf(jp_vtau)%fnow(:,:,1)
184            ENDIF
185         ENDIF
186
187         IF( ln_dm2dc ) THEN   ;   qsr(:,:) = sbc_dcy( sf(jp_qsr)%fnow(:,:,1) )   ! modify now Qsr to include the diurnal cycle
188         ELSE                  ;   qsr(:,:) =          sf(jp_qsr)%fnow(:,:,1)
189         ENDIF
190!CDIR COLLAPSE
191         DO jj = 1, jpj                                           ! set the ocean fluxes from read fields
192            DO ji = 1, jpi
193               utau(ji,jj) = sf(jp_utau)%fnow(ji,jj,1)
194               vtau(ji,jj) = sf(jp_vtau)%fnow(ji,jj,1)
195               qns (ji,jj) = sf(jp_qtot)%fnow(ji,jj,1) - sf(jp_qsr)%fnow(ji,jj,1)
196               emp (ji,jj) = sf(jp_emp )%fnow(ji,jj,1)
197            END DO
198         END DO
199         !                                                        ! add modification due to drag coefficient read from wave forcing
200         !                                                        ! this code is inefficient but put here to allow merging with another UKMO branch
201         IF( ln_shelf_flx .AND. ln_readtau ) THEN
202            IF( ln_cdgw .AND. nn_drag == jp_std ) THEN
203               IF( cpl_wdrag ) THEN 
204                  ! reset utau and vtau to the wind components: the momentum will
205                  ! be calculated from the coupled value of the drag coefficient
206                  DO jj = 1, jpj
207                     DO ji = 1, jpi
208                        utau(ji,jj) = zwnd_i(ji,jj)
209                        vtau(ji,jj) = zwnd_j(ji,jj)
210                     END DO
211                  END DO
212               ELSE
213                  DO jj = 1, jpj
214                     DO ji = 1, jpi
215                        totwind = sqrt(zwnd_i(ji,jj)*zwnd_i(ji,jj) + zwnd_j(ji,jj)*zwnd_j(ji,jj))
216                        utau(ji,jj) = zrhoa * cdn_wave(ji,jj) * zwnd_i(ji,jj) * totwind
217                        vtau(ji,jj) = zrhoa * cdn_wave(ji,jj) * zwnd_j(ji,jj) * totwind
218                     END DO
219                  END DO
220               ENDIF
221            ELSE IF( nn_drag == jp_const ) THEN
222               DO jj = 1, jpj
223                  DO ji = 1, jpi
224                     totwind = sqrt(zwnd_i(ji,jj)*zwnd_i(ji,jj) + zwnd_j(ji,jj)*zwnd_j(ji,jj))
225                     utau(ji,jj) = zrhoa * zcdrag * zwnd_i(ji,jj) * totwind
226                     vtau(ji,jj) = zrhoa * zcdrag * zwnd_j(ji,jj) * totwind
227                  END DO
228               END DO
229            ENDIF
230         ENDIF
231         !                                                        ! add to qns the heat due to e-p
232         qns(:,:) = qns(:,:) - emp(:,:) * sst_m(:,:) * rcp        ! mass flux is at SST
233         !
234         !                                                        ! module of wind stress and wind speed at T-point
235         IF( ln_readtau ) THEN
236         zcoef = 1. / ( zrhoa * zcdrag )
237!CDIR NOVERRCHK
238         DO jj = 2, jpjm1
239!CDIR NOVERRCHK
240            DO ji = fs_2, fs_jpim1   ! vect. opt.
241               ztx = utau(ji-1,jj  ) + utau(ji,jj) 
242               zty = vtau(ji  ,jj-1) + vtau(ji,jj) 
243               zmod = 0.5 * SQRT( ztx * ztx + zty * zty )
244               taum(ji,jj) = zmod
245               IF( ln_shelf_flx ) THEN
246                  ! winds as received, not relative to the current
247                  ztx = sf(jp_utau)%fnow(ji-1,jj  ) + sf(jp_utau)%fnow(ji,jj)
248                  zty = sf(jp_vtau)%fnow(ji  ,jj-1) + sf(jp_vtau)%fnow(ji,jj)
249                  wndm(ji,jj) = 0.5 * SQRT( ztx * ztx + zty * zty )
250               ELSE
251               wndm(ji,jj) = SQRT( zmod * zcoef )
252               ENDIF
253            END DO
254         END DO
255         taum(:,:) = taum(:,:) * tmask(:,:,1) ; wndm(:,:) = wndm(:,:) * tmask(:,:,1)
256         CALL lbc_lnk( taum(:,:), 'T', 1. )   ;   CALL lbc_lnk( wndm(:,:), 'T', 1. )
257         ENDIF
258
259         IF( nitend-nit000 <= 100 .AND. lwp ) THEN                ! control print (if less than 100 time-step asked)
260            WRITE(numout,*) 
261            WRITE(numout,*) '        read daily momentum, heat and freshwater fluxes OK'
262            DO jf = 1, jpfld
263               IF( jf == jp_utau .OR. jf == jp_vtau )   zfact =     1.
264               IF( jf == jp_qtot .OR. jf == jp_qsr  )   zfact =     0.1
265               IF( jf == jp_emp                     )   zfact = 86400.
266               WRITE(numout,*) 
267               WRITE(numout,*) ' day: ', ndastp , TRIM(sf(jf)%clvar), ' * ', zfact
268               CALL prihre( sf(jf)%fnow, jpi, jpj, 1, jpi, 20, 1, jpj, 10, zfact, numout )
269            END DO
270            CALL FLUSH(numout)
271         ENDIF
272         !
273         IF( ln_shelf_flx .AND. ln_readtau ) THEN
274            CALL wrk_dealloc( jpi,jpj, zwnd_i, zwnd_j )
275         ENDIF
276         !
277      ENDIF
278      !
279   END SUBROUTINE sbc_flx
280
281   !!======================================================================
282END MODULE sbcflx
Note: See TracBrowser for help on using the repository browser.