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/2015_V36_STABLE_CO6_CO5_zenv_pomsdwl/NEMOGCM/NEMO/OPA_SRC/SBC – NEMO

source: branches/UKMO/2015_V36_STABLE_CO6_CO5_zenv_pomsdwl/NEMOGCM/NEMO/OPA_SRC/SBC/sbcflx.F90 @ 5654

Last change on this file since 5654 was 5654, checked in by deazer, 9 years ago

Added in changes to allow CO5 like run to verify CO6 with NEMO STABLE VN3.6

File size: 12.7 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 lib_mpp         ! distribued memory computing library
23   USE lbclnk          ! ocean lateral boundary conditions (or mpp link)
24
25   IMPLICIT NONE
26   PRIVATE
27
28   PUBLIC sbc_flx       ! routine called by step.F90
29
30   INTEGER , PARAMETER ::   jpfld   = 6   ! maximum number of files to read
31   INTEGER , PARAMETER ::   jp_utau = 1   ! index of wind stress (i-component) file
32   INTEGER , PARAMETER ::   jp_vtau = 2   ! index of wind stress (j-component) file
33   INTEGER , PARAMETER ::   jp_qtot = 3   ! index of total (non solar+solar) heat file
34   INTEGER , PARAMETER ::   jp_qsr  = 4   ! index of solar heat file
35   INTEGER , PARAMETER ::   jp_emp  = 5   ! index of evaporation-precipation file
36   INTEGER , PARAMETER ::   jp_press = 6  ! index of pressure for UKMO shelf fluxes
37   TYPE(FLD), ALLOCATABLE, DIMENSION(:) ::   sf    ! structure of input fields (file informations, fields read)
38   LOGICAL , PUBLIC    ::   ln_shelf_flx = .FALSE. ! UKMO SHELF specific flux flag
39   INTEGER             ::   jpfld_local   ! maximum number of files to
40read (locally modified depending on ln_shelf_flx) 
41
42   !! * Substitutions
43#  include "domzgr_substitute.h90"
44#  include "vectopt_loop_substitute.h90"
45   !!----------------------------------------------------------------------
46   !! NEMO/OPA 3.3 , NEMO-consortium (2010)
47   !! $Id$
48   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
49   !!----------------------------------------------------------------------
50CONTAINS
51
52   SUBROUTINE sbc_flx( kt )
53      !!---------------------------------------------------------------------
54      !!                    ***  ROUTINE sbc_flx  ***
55      !!                   
56      !! ** Purpose :   provide at each time step the surface ocean fluxes
57      !!                (momentum, heat, freshwater and runoff)
58      !!
59      !! ** Method  : - READ each fluxes in NetCDF files:
60      !!                   i-component of the stress              utau  (N/m2)
61      !!                   j-component of the stress              vtau  (N/m2)
62      !!                   net downward heat flux                 qtot  (watt/m2)
63      !!                   net downward radiative flux            qsr   (watt/m2)
64      !!                   net upward freshwater (evapo - precip) emp   (kg/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 is present (computed in limsbc(_2).F90)
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      REAL     ::   cs                    ! UKMO SHELF: Friction co-efficient at surface
89      REAL     ::   totwindspd            ! UKMO SHELF: Magnitude of wind speed vector
90
91      REAL(wp) ::   rhoa  = 1.22         ! Air density kg/m3
92      REAL(wp) ::   cdrag = 1.5e-3       ! drag coefficient
93      !!
94      CHARACTER(len=100) ::  cn_dir                               ! Root directory for location of flx files
95      TYPE(FLD_N), DIMENSION(jpfld) ::   slf_i                    ! array of namelist information structures
96      TYPE(FLD_N) ::   sn_utau, sn_vtau, sn_qtot, sn_qsr, sn_emp, sn_press  !  informations about the fields to be read
97      LOGICAL     ::   ln_foam_flx  = .FALSE.                     ! UKMO FOAM specific flux flag
98      NAMELIST/namsbc_flx/ cn_dir, sn_utau, sn_vtau, sn_qtot, sn_qsr, sn_emp,   &
99      &                    ln_foam_flx, sn_press, ln_shelf_flx
100      !!---------------------------------------------------------------------
101      !
102      IF( kt == nit000 ) THEN                ! First call kt=nit000 
103         ! set file information
104         REWIND( numnam_ref )              ! Namelist namsbc_flx in reference namelist : Files for fluxes
105         READ  ( numnam_ref, namsbc_flx, IOSTAT = ios, ERR = 901)
106901      IF( ios /= 0 ) CALL ctl_nam ( ios , 'namsbc_flx in reference namelist', lwp )
107
108         REWIND( numnam_cfg )              ! Namelist namsbc_flx in configuration namelist : Files for fluxes
109         READ  ( numnam_cfg, namsbc_flx, IOSTAT = ios, ERR = 902 )
110902      IF( ios /= 0 ) CALL ctl_nam ( ios , 'namsbc_flx in configuration namelist', lwp )
111         IF(lwm) WRITE ( numond, namsbc_flx ) 
112         !
113         !                                         ! check: do we plan to use ln_dm2dc with non-daily forcing?
114         IF( ln_dm2dc .AND. sn_qsr%nfreqh /= 24 )   &
115            &   CALL ctl_stop( 'sbc_blk_core: ln_dm2dc can be activated only with daily short-wave forcing' ) 
116         !
117         !                                         ! store namelist information in an array
118         slf_i(jp_utau) = sn_utau   ;   slf_i(jp_vtau) = sn_vtau
119         slf_i(jp_qtot) = sn_qtot   ;   slf_i(jp_qsr ) = sn_qsr 
120         slf_i(jp_emp ) = sn_emp
121         !
122            ALLOCATE( sf(jpfld), STAT=ierror )        ! set sf structure
123            IF( ln_shelf_flx ) slf_i(jp_press) = sn_press
124   
125            ! define local jpfld depending on shelf_flx logical
126            IF( ln_shelf_flx ) THEN
127               jpfld_local = jpfld
128            ELSE
129               jpfld_local = jpfld-1
130            ENDIF
131            !
132            ALLOCATE( sf(jpfld_local), STAT=ierror )        ! set sf structure
133         IF( ierror > 0 ) THEN   
134            CALL ctl_stop( 'sbc_flx: unable to allocate sf structure' )   ;   RETURN 
135         ENDIF
136         DO ji= 1, jpfld
137            ALLOCATE( sf(ji)%fnow(jpi,jpj,1) )
138            IF( slf_i(ji)%ln_tint ) ALLOCATE( sf(ji)%fdta(jpi,jpj,1,2) )
139         END DO
140         !                                         ! fill sf with slf_i and control print
141         CALL fld_fill( sf, slf_i, cn_dir, 'sbc_flx', 'flux formulation for ocean surface boundary condition', 'namsbc_flx' )
142         !
143         sfx(:,:) = 0.0_wp                         ! salt flux due to freezing/melting (non-zero only if ice is present; set in limsbc(_2).F90)
144         !
145      ENDIF
146
147      CALL fld_read( kt, nn_fsbc, sf )                            ! input fields provided at the current time-step
148     
149      IF( MOD( kt-1, nn_fsbc ) == 0 ) THEN                        ! update ocean fluxes at each SBC frequency
150
151         IF( ln_dm2dc ) THEN   ;   qsr(:,:) = sbc_dcy( sf(jp_qsr)%fnow(:,:,1) )   ! modify now Qsr to include the diurnal cycle
152         ELSE                  ;   qsr(:,:) =          sf(jp_qsr)%fnow(:,:,1)
153         ENDIF
154!CDIR COLLAPSE
155            !!UKMO SHELF effect of atmospheric pressure on SSH
156            ! If using ln_apr_dyn, this is done there so don't repeat here.
157            IF( ln_shelf_flx .AND. .NOT. ln_apr_dyn) THEN
158               DO jj = 1, jpjm1
159                  DO ji = 1, jpim1
160                     apgu(ji,jj) = (-1.0/rau0)*(sf(jp_press)%fnow(ji+1,jj,1)-sf(jp_press)%fnow(ji,jj,1))/e1u(ji,jj)
161                     apgv(ji,jj) = (-1.0/rau0)*(sf(jp_press)%fnow(ji,jj+1,1)-sf(jp_press)%fnow(ji,jj,1))/e2v(ji,jj)
162                  END DO
163               END DO
164            ENDIF ! ln_shelf_flx
165     
166         DO jj = 1, jpj                                           ! set the ocean fluxes from read fields
167            DO ji = 1, jpi
168                   IF( ln_shelf_flx ) THEN
169                      !! UKMO SHELF - need atmospheric pressure to calculate Haney forcing
170                      pressnow(ji,jj) = sf(jp_press)%fnow(ji,jj,1)
171                      !! UKMO SHELF flux files contain wind speed not wind stress
172                      totwindspd = sqrt((sf(jp_utau)%fnow(ji,jj,1))**2.0 + (sf(jp_vtau)%fnow(ji,jj,1))**2.0)
173                      cs = 0.63 + (0.066 * totwindspd)
174                      utau(ji,jj) = cs * (rhoa/rau0) * sf(jp_utau)%fnow(ji,jj,1) * totwindspd
175                      vtau(ji,jj) = cs * (rhoa/rau0) * sf(jp_vtau)%fnow(ji,jj,1) * totwindspd
176                   ELSE
177                      utau(ji,jj) = sf(jp_utau)%fnow(ji,jj,1)
178                      vtau(ji,jj) = sf(jp_vtau)%fnow(ji,jj,1)
179                   ENDIF
180                   qsr (ji,jj) = sf(jp_qsr )%fnow(ji,jj,1)
181                   IF( ln_foam_flx .OR. ln_shelf_flx ) THEN
182                      !! UKMO FOAM flux files contain non-solar heat flux (qns) rather than total heat flux (qtot)
183                      qns (ji,jj) = sf(jp_qtot)%fnow(ji,jj,1)
184                      !! UKMO FOAM flux files contain the net DOWNWARD freshwater flux P-E rather then E-P
185                      emp (ji,jj) = -1. * sf(jp_emp )%fnow(ji,jj,1)
186                   ELSE
187                      qns (ji,jj) = sf(jp_qtot)%fnow(ji,jj,1) - sf(jp_qsr)%fnow(ji,jj,1)
188                      emp (ji,jj) = sf(jp_emp )%fnow(ji,jj,1)
189                   ENDIF
190            END DO
191         END DO
192         !                                                        ! add to qns the heat due to e-p
193         qns(:,:) = qns(:,:) - emp(:,:) * sst_m(:,:) * rcp        ! mass flux is at SST
194         !
195   
196            !! UKMO FOAM wind fluxes need lbc_lnk calls owing to a bug in interp.exe
197            IF( ln_foam_flx ) THEN
198               CALL lbc_lnk( utau(:,:), 'U', -1. )
199               CALL lbc_lnk( vtau(:,:), 'V', -1. )
200            ENDIF
201   
202         !                                                        ! module of wind stress and wind speed at T-point
203         zcoef = 1. / ( zrhoa * zcdrag )
204!CDIR NOVERRCHK
205         DO jj = 2, jpjm1
206!CDIR NOVERRCHK
207            DO ji = fs_2, fs_jpim1   ! vect. opt.
208               ztx = utau(ji-1,jj  ) + utau(ji,jj) 
209               zty = vtau(ji  ,jj-1) + vtau(ji,jj) 
210               zmod = 0.5 * SQRT( ztx * ztx + zty * zty )
211               taum(ji,jj) = zmod
212               wndm(ji,jj) = SQRT( zmod * zcoef )
213            END DO
214         END DO
215         taum(:,:) = taum(:,:) * tmask(:,:,1) ; wndm(:,:) = wndm(:,:) * tmask(:,:,1)
216         CALL lbc_lnk( taum(:,:), 'T', 1. )   ;   CALL lbc_lnk( wndm(:,:), 'T', 1. )
217
218         IF( nitend-nit000 <= 100 .AND. lwp ) THEN                ! control print (if less than 100 time-step asked)
219            WRITE(numout,*) 
220            WRITE(numout,*) '        read daily momentum, heat and freshwater fluxes OK'
221            DO jf = 1, jpfld_local
222               IF( jf == jp_utau .OR. jf == jp_vtau )   zfact =     1.
223               IF( jf == jp_qtot .OR. jf == jp_qsr  )   zfact =     0.1
224               IF( jf == jp_emp                     )   zfact = 86400.
225               WRITE(numout,*) 
226               WRITE(numout,*) ' day: ', ndastp , TRIM(sf(jf)%clvar), ' * ', zfact
227               CALL prihre( sf(jf)%fnow, jpi, jpj, 1, jpi, 20, 1, jpj, 10, zfact, numout )
228            END DO
229            CALL FLUSH(numout)
230         ENDIF
231         !
232      ENDIF
233      !
234   END SUBROUTINE sbc_flx
235
236   !!======================================================================
237END MODULE sbcflx
Note: See TracBrowser for help on using the repository browser.