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

source: branches/UKMO/dev_3841_sbc/NEMOGCM/NEMO/OPA_SRC/SBC/sbcflx.F90 @ 4827

Last change on this file since 4827 was 4827, checked in by charris, 9 years ago

Some demonstration code changes.

  • Property svn:keywords set to Id
File size: 7.1 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 fldread2        ! read input fields
20   USE fld_def
21   USE sbcget
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   !! * Substitutions
33#  include "domzgr_substitute.h90"
34#  include "vectopt_loop_substitute.h90"
35   !!----------------------------------------------------------------------
36   !! NEMO/OPA 3.3 , NEMO-consortium (2010)
37   !! $Id$
38   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
39   !!----------------------------------------------------------------------
40CONTAINS
41
42   SUBROUTINE sbc_flx( kt )
43      !!---------------------------------------------------------------------
44      !!                    ***  ROUTINE sbc_flx  ***
45      !!                   
46      !! ** Purpose :   provide at each time step the surface ocean fluxes
47      !!                (momentum, heat, freshwater and runoff)
48      !!
49      !! ** Method  : - READ each fluxes in NetCDF files:
50      !!                   i-component of the stress              utau  (N/m2)
51      !!                   j-component of the stress              vtau  (N/m2)
52      !!                   net downward heat flux                 qtot  (watt/m2)
53      !!                   net downward radiative flux            qsr   (watt/m2)
54      !!                   net upward freshwater (evapo - precip) emp   (kg/m2/s)
55      !!
56      !!      CAUTION :  - never mask the surface stress fields
57      !!                 - the stress is assumed to be in the (i,j) mesh referential
58      !!
59      !! ** Action  :   update at each time-step
60      !!              - utau, vtau  i- and j-component of the wind stress
61      !!              - taum        wind stress module at T-point
62      !!              - wndm        10m wind module at T-point
63      !!              - qns         non solar heat flux including heat flux due to emp
64      !!              - qsr         solar heat flux
65      !!              - emp         upward mass flux (evap. - precip.)
66      !!              - sfx         salt flux; set to zero at nit000 but possibly non-zero
67      !!                            if ice is present (computed in limsbc(_2).F90)
68      !!----------------------------------------------------------------------
69      INTEGER, INTENT(in) ::   kt   ! ocean time step
70      !!
71      INTEGER  ::   ji, jj, jf            ! dummy indices
72      REAL(wp) ::   zfact                 ! temporary scalar
73      REAL(wp) ::   zrhoa  = 1.22         ! Air density kg/m3
74      REAL(wp) ::   zcdrag = 1.5e-3       ! drag coefficient
75      REAL(wp) ::   ztx, zty, zmod, zcoef ! temporary variables
76      !!
77!      CHARACTER(len=100) ::  cn_dir                               ! Root directory for location of flx files
78!      NAMELIST/namsbc_flx/ cn_dir, sn_utau, sn_vtau, sn_qtot, sn_qsr, sn_emp
79      !!---------------------------------------------------------------------
80      !
81      IF( kt == nit000 ) THEN                ! First call kt=nit000 
82         !
83         !                                         ! check: do we plan to use ln_dm2dc with non-daily forcing?
84         IF( ln_dm2dc .AND. sf(jp_qsroce)%nfreqh /= 24 )   &
85            &   CALL ctl_stop( 'sbc_blk_core: ln_dm2dc can be activated only with daily short-wave forcing' ) 
86         !
87         sfx(:,:) = 0.0_wp                         ! salt flux due to freezing/melting (non-zero only if ice is present; set in limsbc(_2).F90)
88         !
89      ENDIF
90
91      IF( MOD( kt-1, nn_fsbc ) == 0 ) THEN                        ! update ocean fluxes at each SBC frequency
92
93         IF( ln_dm2dc ) THEN   ;   qsr(:,:) = sbc_dcy( sf(jp_qsroce)%fnow(:,:,1) )   ! modify now Qsr to include the diurnal cycle
94         ELSE                  ;   qsr(:,:) =          sf(jp_qsroce)%fnow(:,:,1)
95         ENDIF
96!CDIR COLLAPSE
97         DO jj = 1, jpj                                           ! set the ocean fluxes from read fields
98            DO ji = 1, jpi
99               utau(ji,jj) = sf(jp_otx1)%fnow(ji,jj,1)
100               vtau(ji,jj) = sf(jp_oty1)%fnow(ji,jj,1)
101               qns (ji,jj) = sf(jp_qtot)%fnow(ji,jj,1) - sf(jp_qsroce)%fnow(ji,jj,1)
102               emp (ji,jj) = sf(jp_oemp )%fnow(ji,jj,1)
103            END DO
104         END DO
105         !                                                        ! add to qns the heat due to e-p
106         qns(:,:) = qns(:,:) - emp(:,:) * sst_m(:,:) * rcp        ! mass flux is at SST
107         !
108         !                                                        ! module of wind stress and wind speed at T-point
109         zcoef = 1. / ( zrhoa * zcdrag )
110!CDIR NOVERRCHK
111         DO jj = 2, jpjm1
112!CDIR NOVERRCHK
113            DO ji = fs_2, fs_jpim1   ! vect. opt.
114               ztx = utau(ji-1,jj  ) + utau(ji,jj) 
115               zty = vtau(ji  ,jj-1) + vtau(ji,jj) 
116               zmod = 0.5 * SQRT( ztx * ztx + zty * zty )
117               taum(ji,jj) = zmod
118               wndm(ji,jj) = SQRT( zmod * zcoef )
119            END DO
120         END DO
121         CALL lbc_lnk( taum(:,:), 'T', 1. )   ;   CALL lbc_lnk( wndm(:,:), 'T', 1. )
122
123         IF( nitend-nit000 <= 100 .AND. lwp ) THEN                ! control print (if less than 100 time-step asked)
124            WRITE(numout,*) 
125            WRITE(numout,*) '        read daily momentum, heat and freshwater fluxes OK'
126            DO jf = 1, jpfld
127               IF( jf == jp_otx1 .OR. jf == jp_oty1   )   zfact =     1.
128               IF( jf == jp_qtot .OR. jf == jp_qsroce )   zfact =     0.1
129               IF( jf == jp_oemp                       )   zfact = 86400.
130               WRITE(numout,*) 
131               WRITE(numout,*) ' day: ', ndastp , TRIM(sf(jf)%clvar), ' * ', zfact
132               CALL prihre( sf(jf)%fnow, jpi, jpj, 1, jpi, 20, 1, jpj, 10, zfact, numout )
133            END DO
134            CALL FLUSH(numout)
135         ENDIF
136         !
137      ENDIF
138      !
139   END SUBROUTINE sbc_flx
140
141   !!======================================================================
142END MODULE sbcflx
Note: See TracBrowser for help on using the repository browser.