1 | MODULE 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 trc_oce ! share SMS/Ocean variables |
---|
18 | USE sbcdcy ! surface boundary condition: diurnal cycle on qsr |
---|
19 | USE phycst ! physical constants |
---|
20 | ! |
---|
21 | USE fldread ! read input fields |
---|
22 | USE iom ! IOM library |
---|
23 | USE in_out_manager ! I/O manager |
---|
24 | USE lib_mpp ! distribued memory computing library |
---|
25 | USE lbclnk ! ocean lateral boundary conditions (or mpp link) |
---|
26 | |
---|
27 | IMPLICIT NONE |
---|
28 | PRIVATE |
---|
29 | |
---|
30 | PUBLIC sbc_flx ! routine called by step.F90 |
---|
31 | |
---|
32 | INTEGER , PARAMETER :: jp_utau = 1 ! index of wind stress (i-component) file |
---|
33 | INTEGER , PARAMETER :: jp_vtau = 2 ! index of wind stress (j-component) file |
---|
34 | INTEGER , PARAMETER :: jp_qtot = 3 ! index of total (non solar+solar) heat file |
---|
35 | INTEGER , PARAMETER :: jp_qsr = 4 ! index of solar heat file |
---|
36 | INTEGER , PARAMETER :: jp_emp = 5 ! index of evaporation-precipation file |
---|
37 | !!INTEGER , PARAMETER :: jp_sfx = 6 ! index of salt flux flux |
---|
38 | INTEGER , PARAMETER :: jpfld = 5 !! 6 ! maximum number of files to read |
---|
39 | |
---|
40 | TYPE(FLD), ALLOCATABLE, DIMENSION(:) :: sf ! structure of input fields (file informations, fields read) |
---|
41 | |
---|
42 | !! * Substitutions |
---|
43 | # include "vectopt_loop_substitute.h90" |
---|
44 | !!---------------------------------------------------------------------- |
---|
45 | !! NEMO/OCE 4.0 , NEMO Consortium (2018) |
---|
46 | !! $Id$ |
---|
47 | !! Software governed by the CeCILL license (see ./LICENSE) |
---|
48 | !!---------------------------------------------------------------------- |
---|
49 | CONTAINS |
---|
50 | |
---|
51 | SUBROUTINE sbc_flx( kt ) |
---|
52 | !!--------------------------------------------------------------------- |
---|
53 | !! *** ROUTINE sbc_flx *** |
---|
54 | !! |
---|
55 | !! ** Purpose : provide at each time step the surface ocean fluxes |
---|
56 | !! (momentum, heat, freshwater and runoff) |
---|
57 | !! |
---|
58 | !! ** Method : - READ each fluxes in NetCDF files: |
---|
59 | !! i-component of the stress utau (N/m2) |
---|
60 | !! j-component of the stress vtau (N/m2) |
---|
61 | !! net downward heat flux qtot (watt/m2) |
---|
62 | !! net downward radiative flux qsr (watt/m2) |
---|
63 | !! net upward freshwater (evapo - precip) emp (kg/m2/s) |
---|
64 | !! salt flux sfx (pss*dh*rho/dt => g/m2/s) |
---|
65 | !! |
---|
66 | !! CAUTION : - never mask the surface stress fields |
---|
67 | !! - the stress is assumed to be in the (i,j) mesh referential |
---|
68 | !! |
---|
69 | !! ** Action : update at each time-step |
---|
70 | !! - utau, vtau i- and j-component of the wind stress |
---|
71 | !! - taum wind stress module at T-point |
---|
72 | !! - wndm 10m wind module at T-point |
---|
73 | !! - qns non solar heat flux including heat flux due to emp |
---|
74 | !! - qsr solar heat flux |
---|
75 | !! - emp upward mass flux (evap. - precip.) |
---|
76 | !! - sfx salt flux; set to zero at nit000 but possibly non-zero |
---|
77 | !! if ice |
---|
78 | !!---------------------------------------------------------------------- |
---|
79 | INTEGER, INTENT(in) :: kt ! ocean time step |
---|
80 | !! |
---|
81 | INTEGER :: ji, jj, jf ! dummy indices |
---|
82 | INTEGER :: ierror ! return error code |
---|
83 | INTEGER :: ios ! Local integer output status for namelist read |
---|
84 | REAL(wp) :: zfact ! temporary scalar |
---|
85 | REAL(wp) :: zrhoa = 1.22 ! Air density kg/m3 |
---|
86 | REAL(wp) :: zcdrag = 1.5e-3 ! drag coefficient |
---|
87 | REAL(wp) :: ztx, zty, zmod, zcoef ! temporary variables |
---|
88 | !! |
---|
89 | CHARACTER(len=100) :: cn_dir ! Root directory for location of flx files |
---|
90 | TYPE(FLD_N), DIMENSION(jpfld) :: slf_i ! array of namelist information structures |
---|
91 | TYPE(FLD_N) :: sn_utau, sn_vtau, sn_qtot, sn_qsr, sn_emp !!, sn_sfx ! informations about the fields to be read |
---|
92 | NAMELIST/namsbc_flx/ cn_dir, sn_utau, sn_vtau, sn_qtot, sn_qsr, sn_emp !!, sn_sfx |
---|
93 | !!--------------------------------------------------------------------- |
---|
94 | ! |
---|
95 | IF( kt == nit000 ) THEN ! First call kt=nit000 |
---|
96 | ! set file information |
---|
97 | REWIND( numnam_ref ) ! Namelist namsbc_flx in reference namelist : Files for fluxes |
---|
98 | READ ( numnam_ref, namsbc_flx, IOSTAT = ios, ERR = 901) |
---|
99 | 901 IF( ios /= 0 ) CALL ctl_nam ( ios , 'namsbc_flx in reference namelist' ) |
---|
100 | |
---|
101 | REWIND( numnam_cfg ) ! Namelist namsbc_flx in configuration namelist : Files for fluxes |
---|
102 | READ ( numnam_cfg, namsbc_flx, IOSTAT = ios, ERR = 902 ) |
---|
103 | 902 IF( ios > 0 ) CALL ctl_nam ( ios , 'namsbc_flx in configuration namelist' ) |
---|
104 | IF(lwm) WRITE ( numond, namsbc_flx ) |
---|
105 | ! |
---|
106 | ! ! check: do we plan to use ln_dm2dc with non-daily forcing? |
---|
107 | IF( ln_dm2dc .AND. sn_qsr%freqh /= 24. ) & |
---|
108 | & CALL ctl_stop( 'sbc_blk_core: ln_dm2dc can be activated only with daily short-wave forcing' ) |
---|
109 | ! |
---|
110 | ! ! store namelist information in an array |
---|
111 | slf_i(jp_utau) = sn_utau ; slf_i(jp_vtau) = sn_vtau |
---|
112 | slf_i(jp_qtot) = sn_qtot ; slf_i(jp_qsr ) = sn_qsr |
---|
113 | slf_i(jp_emp ) = sn_emp !! ; slf_i(jp_sfx ) = sn_sfx |
---|
114 | ! |
---|
115 | ALLOCATE( sf(jpfld), STAT=ierror ) ! set sf structure |
---|
116 | IF( ierror > 0 ) THEN |
---|
117 | CALL ctl_stop( 'sbc_flx: unable to allocate sf structure' ) ; RETURN |
---|
118 | ENDIF |
---|
119 | DO ji= 1, jpfld |
---|
120 | ALLOCATE( sf(ji)%fnow(jpi,jpj,1) ) |
---|
121 | IF( slf_i(ji)%ln_tint ) ALLOCATE( sf(ji)%fdta(jpi,jpj,1,2) ) |
---|
122 | END DO |
---|
123 | ! ! fill sf with slf_i and control print |
---|
124 | CALL fld_fill( sf, slf_i, cn_dir, 'sbc_flx', 'flux formulation for ocean surface boundary condition', 'namsbc_flx' ) |
---|
125 | ! |
---|
126 | ENDIF |
---|
127 | |
---|
128 | CALL fld_read( kt, nn_fsbc, sf ) ! input fields provided at the current time-step |
---|
129 | |
---|
130 | IF( MOD( kt-1, nn_fsbc ) == 0 ) THEN ! update ocean fluxes at each SBC frequency |
---|
131 | |
---|
132 | IF( ln_dm2dc ) THEN ; qsr(:,:) = sbc_dcy( sf(jp_qsr)%fnow(:,:,1) ) * tmask(:,:,1) ! modify now Qsr to include the diurnal cycle |
---|
133 | ELSE ; qsr(:,:) = sf(jp_qsr)%fnow(:,:,1) * tmask(:,:,1) |
---|
134 | ENDIF |
---|
135 | #if defined key_top |
---|
136 | IF( ln_trcdc2dm ) THEN ! diurnal cycle in TOP |
---|
137 | IF( ln_dm2dc ) THEN ; qsr_mean(:,:) = sf(jp_qsr)%fnow(:,:,1) * tmask(:,:,1) |
---|
138 | ELSE ; ncpl_qsr_freq = sf(jp_qsr)%freqh * 3600 ! qsr_mean will be computed in TOP |
---|
139 | ENDIF |
---|
140 | ENDIF |
---|
141 | #endif |
---|
142 | DO jj = 1, jpj ! set the ocean fluxes from read fields |
---|
143 | DO ji = 1, jpi |
---|
144 | utau(ji,jj) = sf(jp_utau)%fnow(ji,jj,1) * umask(ji,jj,1) |
---|
145 | vtau(ji,jj) = sf(jp_vtau)%fnow(ji,jj,1) * vmask(ji,jj,1) |
---|
146 | qns (ji,jj) = ( sf(jp_qtot)%fnow(ji,jj,1) - sf(jp_qsr)%fnow(ji,jj,1) ) * tmask(ji,jj,1) |
---|
147 | emp (ji,jj) = sf(jp_emp )%fnow(ji,jj,1) * tmask(ji,jj,1) |
---|
148 | !!sfx (ji,jj) = sf(jp_sfx )%fnow(ji,jj,1) * tmask(ji,jj,1) |
---|
149 | END DO |
---|
150 | END DO |
---|
151 | ! ! add to qns the heat due to e-p |
---|
152 | !clem: I do not think it is needed |
---|
153 | !!qns(:,:) = qns(:,:) - emp(:,:) * sst_m(:,:) * rcp ! mass flux is at SST |
---|
154 | ! |
---|
155 | ! clem: without these lbc calls, it seems that the northfold is not ok (true in 3.6, not sure in 4.x) |
---|
156 | CALL lbc_lnk_multi( 'sbcflx', utau, 'U', -1._wp, vtau, 'V', -1._wp, & |
---|
157 | & qns, 'T', 1._wp, emp , 'T', 1._wp, qsr, 'T', 1._wp ) !! sfx, 'T', 1._wp ) |
---|
158 | ! |
---|
159 | IF( nitend-nit000 <= 100 .AND. lwp ) THEN ! control print (if less than 100 time-step asked) |
---|
160 | WRITE(numout,*) |
---|
161 | WRITE(numout,*) ' read daily momentum, heat and freshwater fluxes OK' |
---|
162 | DO jf = 1, jpfld |
---|
163 | IF( jf == jp_utau .OR. jf == jp_vtau ) zfact = 1. |
---|
164 | IF( jf == jp_qtot .OR. jf == jp_qsr ) zfact = 0.1 |
---|
165 | IF( jf == jp_emp ) zfact = 86400. |
---|
166 | WRITE(numout,*) |
---|
167 | WRITE(numout,*) ' day: ', ndastp , TRIM(sf(jf)%clvar), ' * ', zfact |
---|
168 | END DO |
---|
169 | ENDIF |
---|
170 | ! |
---|
171 | ENDIF |
---|
172 | ! ! module of wind stress and wind speed at T-point |
---|
173 | ! Note the use of 0.5*(2-umask) in order to unmask the stress along coastlines |
---|
174 | zcoef = 1. / ( zrhoa * zcdrag ) |
---|
175 | DO jj = 2, jpjm1 |
---|
176 | DO ji = fs_2, fs_jpim1 ! vect. opt. |
---|
177 | ztx = ( utau(ji-1,jj ) + utau(ji,jj) ) * 0.5_wp * ( 2._wp - MIN( umask(ji-1,jj ,1), umask(ji,jj,1) ) ) |
---|
178 | zty = ( vtau(ji ,jj-1) + vtau(ji,jj) ) * 0.5_wp * ( 2._wp - MIN( vmask(ji ,jj-1,1), vmask(ji,jj,1) ) ) |
---|
179 | zmod = SQRT( ztx * ztx + zty * zty ) * tmask(ji,jj,1) |
---|
180 | taum(ji,jj) = zmod |
---|
181 | wndm(ji,jj) = SQRT( zmod * zcoef ) !!clem: not used? |
---|
182 | END DO |
---|
183 | END DO |
---|
184 | ! |
---|
185 | CALL lbc_lnk_multi( 'sbcflx', taum, 'T', 1._wp, wndm, 'T', 1._wp ) |
---|
186 | ! |
---|
187 | ! |
---|
188 | END SUBROUTINE sbc_flx |
---|
189 | |
---|
190 | !!====================================================================== |
---|
191 | END MODULE sbcflx |
---|