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

source: branches/dev_r2174_DCY/NEMO/OPA_SRC/SBC/sbcflx.F90 @ 2187

Last change on this file since 2187 was 2187, checked in by smasson, 14 years ago

add diurna cycle in dev_r2174_DCY, see ticket:730

  • Property svn:keywords set to Id
File size: 10.0 KB
Line 
1MODULE sbcflx
2   !!======================================================================
3   !!                       ***  MODULE  sbcflx  ***
4   !! Ocean forcing:  momentum, heat and freshwater flux formulation
5   !!=====================================================================
6   !! History :  9.0   !  06-06  (G. Madec)  Original code
7   !!----------------------------------------------------------------------
8
9   !!----------------------------------------------------------------------
10   !!   namflx   : flux formulation namlist
11   !!   sbc_flx  : flux formulation as ocean surface boundary condition
12   !!              (forced mode, fluxes read in NetCDF files)
13   !!----------------------------------------------------------------------
14   !! question diverses
15   !!  *   ajouter un test sur la division entier de freqh et rdttra ???
16   !!  **  ajoute dans namelist: 1 year forcing files
17   !!                         or forcing file starts at the begining of the run
18   !!  *** we assume that the forcing file start and end with the previous
19   !!      year last record and the next year first record (useful for
20   !!      time interpolation, required even if no time interp???)
21   !!  *   ajouter un test sur la division de la frequence en pas de temps
22   !!  ==> daymod ajout de nsec_year = number of second since the begining of the year
23   !!      assumed to be 0 at 0h january the 1st (i.e. 24h december the 31)
24   !!
25   !!  *** regrouper dtatem et dtasal
26   !!----------------------------------------------------------------------
27   USE oce             ! ocean dynamics and tracers
28   USE dom_oce         ! ocean space and time domain
29   USE sbc_oce         ! Surface boundary condition: ocean fields
30   USE phycst          ! physical constants
31   USE sbcdcy          ! diurnal cycle on qsr
32   USE fldread         ! read input fields
33   USE iom             ! IOM library
34   USE in_out_manager  ! I/O manager
35   USE lib_mpp         ! distribued memory computing library
36   USE lbclnk          ! ocean lateral boundary conditions (or mpp link)
37
38   IMPLICIT NONE
39   PRIVATE
40
41   PUBLIC sbc_flx       ! routine called by step.F90
42
43   INTEGER , PARAMETER ::   jpfld   = 5   ! maximum number of files to read
44   INTEGER , PARAMETER ::   jp_utau = 1   ! index of wind stress (i-component) file
45   INTEGER , PARAMETER ::   jp_vtau = 2   ! index of wind stress (j-component) file
46   INTEGER , PARAMETER ::   jp_qtot = 3   ! index of total (non solar+solar) heat file
47   INTEGER , PARAMETER ::   jp_qsr  = 4   ! index of solar heat file
48   INTEGER , PARAMETER ::   jp_emp  = 5   ! index of evaporation-precipation file
49   TYPE(FLD), ALLOCATABLE, DIMENSION(:) ::   sf    ! structure of input fields (file informations, fields read)
50
51   !! * Substitutions
52#  include "domzgr_substitute.h90"
53#  include "vectopt_loop_substitute.h90"
54   !!----------------------------------------------------------------------
55   !!   OPA 9.0 , LOCEAN-IPSL (2006)
56   !! $Id$
57   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt)
58   !!----------------------------------------------------------------------
59
60CONTAINS
61
62   SUBROUTINE sbc_flx( kt )
63      !!---------------------------------------------------------------------
64      !!                    ***  ROUTINE sbc_flx  ***
65      !!                   
66      !! ** Purpose :   provide at each time step the surface ocean fluxes
67      !!                (momentum, heat, freshwater and runoff)
68      !!
69      !! ** Method  : - READ each fluxes in NetCDF files:
70      !!                   i-component of the stress              utau  (N/m2)
71      !!                   j-component of the stress              vtau  (N/m2)
72      !!                   net downward heat flux                 qtot  (watt/m2)
73      !!                   net downward radiative flux            qsr   (watt/m2)
74      !!                   net upward freshwater (evapo - precip) emp   (kg/m2/s)
75      !!
76      !!      CAUTION :  - never mask the surface stress fields
77      !!                 - the stress is assumed to be in the mesh referential
78      !!                   i.e. the (i,j) referential
79      !!
80      !! ** Action  :   update at each time-step
81      !!              - utau, vtau  i- and j-component of the wind stress
82      !!              - taum        wind stress module at T-point
83      !!              - wndm        10m wind module at T-point
84      !!              - qns, qsr    non-slor and solar heat flux
85      !!              - emp, emps   evaporation minus precipitation
86      !!----------------------------------------------------------------------
87      INTEGER, INTENT(in) ::   kt   ! ocean time step
88      !!
89      INTEGER  ::   ji, jj, jf            ! dummy indices
90      INTEGER  ::   ierror                ! return error code
91      REAL(wp) ::   zfact                 ! temporary scalar
92      REAL(wp) ::   zrhoa  = 1.22         ! Air density kg/m3
93      REAL(wp) ::   zcdrag = 1.5e-3       ! drag coefficient
94      REAL(wp) ::   ztx, zty, zmod, zcoef ! temporary variables
95      !!
96      CHARACTER(len=100) ::  cn_dir                               ! Root directory for location of flx files
97      TYPE(FLD_N), DIMENSION(jpfld) ::   slf_i                    ! array of namelist information structures
98      TYPE(FLD_N) ::   sn_utau, sn_vtau, sn_qtot, sn_qsr, sn_emp  ! informations about the fields to be read
99      NAMELIST/namsbc_flx/ cn_dir, sn_utau, sn_vtau, sn_qtot, sn_qsr, sn_emp
100      !!---------------------------------------------------------------------
101      !                                         ! ====================== !
102      IF( kt == nit000 ) THEN                   !  First call kt=nit000  !
103         !                                      ! ====================== !
104         ! set file information
105         cn_dir = './'        ! directory in which the model is executed
106         ! ... default values (NB: frequency positive => hours, negative => months)
107         !              !   file    ! frequency !  variable  ! time intep !  clim   ! 'yearly' or ! weights  ! rotation   !
108         !              !   name    !  (hours)  !   name     !   (T/F)    !  (T/F)  !  'monthly'  ! filename ! pairs      !
109         sn_utau = FLD_N(   'utau'  ,    24     ,  'utau'    ,  .false.   , .false. ,   'yearly'  , ''       , ''         )
110         sn_vtau = FLD_N(   'vtau'  ,    24     ,  'vtau'    ,  .false.   , .false. ,   'yearly'  , ''       , ''         )
111         sn_qtot = FLD_N(   'qtot'  ,    24     ,  'qtot'    ,  .false.   , .false. ,   'yearly'  , ''       , ''         )
112         sn_qsr  = FLD_N(   'qsr'   ,    24     ,  'qsr'     ,  .false.   , .false. ,   'yearly'  , ''       , ''         )
113         sn_emp  = FLD_N(   'emp'   ,    24     ,  'emp'     ,  .false.   , .false. ,   'yearly'  , ''       , ''         )
114
115         REWIND ( numnam )               ! ... read in namlist namflx
116         READ   ( numnam, namsbc_flx ) 
117
118         ! do we plan to use ln_dm2dc with non-daily forcing?
119         IF( ln_dm2dc .AND. sn_qsr%nfreqh /= 24 )   &
120            &   CALL ctl_stop( 'sbc_blk_core: ln_dm2dc can be activated only with daily short-wave forcing' ) 
121
122         ! store namelist information in an array
123         slf_i(jp_utau) = sn_utau   ;   slf_i(jp_vtau) = sn_vtau
124         slf_i(jp_qtot) = sn_qtot   ;   slf_i(jp_qsr ) = sn_qsr 
125         slf_i(jp_emp ) = sn_emp
126
127         ! set sf structure
128         ALLOCATE( sf(jpfld), STAT=ierror )
129         IF( ierror > 0 ) THEN   
130            CALL ctl_stop( 'sbc_flx: unable to allocate sf structure' )   ;   RETURN 
131         ENDIF
132         DO ji= 1, jpfld
133            ALLOCATE( sf(ji)%fnow(jpi,jpj) )
134            ALLOCATE( sf(ji)%fdta(jpi,jpj,2) )
135         END DO
136
137
138         ! fill sf with slf_i and control print
139         CALL fld_fill( sf, slf_i, cn_dir, 'sbc_flx', 'flux formulation for ocean surface boundary condition', 'namsbc_flx' )
140         !
141      ENDIF
142
143      CALL fld_read( kt, nn_fsbc, sf )           ! Read input fields and provides the
144      !                                          ! input fields at the current time-step
145      IF( ln_dm2dc )   CALL sbc_dcy( kt , sf(jp_qsr)%fnow )   ! modify sf(jp_qsr)%fnow for diurnal cycle
146
147      IF( MOD( kt-1, nn_fsbc ) == 0 ) THEN
148         !
149         ! set the ocean fluxes from read fields
150!CDIR COLLAPSE
151         DO jj = 1, jpj
152            DO ji = 1, jpi
153               utau(ji,jj) = sf(jp_utau)%fnow(ji,jj)
154               vtau(ji,jj) = sf(jp_vtau)%fnow(ji,jj)
155               qns (ji,jj) = sf(jp_qtot)%fnow(ji,jj) - sf(jp_qsr)%fnow(ji,jj)
156               qsr (ji,jj) = sf(jp_qsr )%fnow(ji,jj)
157               emp (ji,jj) = sf(jp_emp )%fnow(ji,jj)
158            END DO
159         END DO
160         
161         ! module of wind stress and wind speed at T-point
162         zcoef = 1. / ( zrhoa * zcdrag ) 
163!CDIR NOVERRCHK
164         DO jj = 2, jpjm1
165!CDIR NOVERRCHK
166            DO ji = fs_2, fs_jpim1   ! vect. opt.
167               ztx = utau(ji-1,jj  ) + utau(ji,jj) 
168               zty = vtau(ji  ,jj-1) + vtau(ji,jj) 
169               zmod = 0.5 * SQRT( ztx * ztx + zty * zty )
170               taum(ji,jj) = zmod
171               wndm(ji,jj) = SQRT( zmod * zcoef )
172            END DO
173         END DO
174         CALL lbc_lnk( taum(:,:), 'T', 1. )   ;   CALL lbc_lnk( wndm(:,:), 'T', 1. )
175
176         ! Initialization of emps (when no ice model)
177         emps(:,:) = emp (:,:) 
178                 
179         ! control print (if less than 100 time-step asked)
180         IF( nitend-nit000 <= 100 .AND. lwp ) THEN
181            WRITE(numout,*) 
182            WRITE(numout,*) '        read daily momentum, heat and freshwater fluxes OK'
183            DO jf = 1, jpfld
184               IF( jf == jp_utau .OR. jf == jp_vtau )   zfact =     1.
185               IF( jf == jp_qtot .OR. jf == jp_qsr  )   zfact =     0.1
186               IF( jf == jp_emp                     )   zfact = 86400.
187               WRITE(numout,*) 
188               WRITE(numout,*) ' day: ', ndastp , TRIM(sf(jf)%clvar), ' * ', zfact
189               CALL prihre( sf(jf)%fnow, jpi, jpj, 1, jpi, 20, 1, jpj, 10, zfact, numout )
190            END DO
191            CALL FLUSH(numout)
192         ENDIF
193         !
194      ENDIF
195      !
196   END SUBROUTINE sbc_flx
197
198   !!======================================================================
199END MODULE sbcflx
Note: See TracBrowser for help on using the repository browser.