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

source: trunk/NEMO/OPA_SRC/SBC/sbcflx.F90 @ 1037

Last change on this file since 1037 was 1037, checked in by ctlod, 16 years ago

trunk: replace freeze(:,:) variable with fr_i(:,:), use the tfreez function defined in eosbn2.F90 and remove the useless ocfzpt.F90 module, see ticket: #177

File size: 11.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 daymod          ! calendar
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   REAL(wp) ::   rhoa  = 1.22         ! Air density kg/m3
52   REAL(wp) ::   cdrag = 1.5e-3       ! drag coefficient
53
54   !! * Substitutions
55#  include "domzgr_substitute.h90"
56#  include "vectopt_loop_substitute.h90"
57   !!----------------------------------------------------------------------
58   !!   OPA 9.0 , LOCEAN-IPSL (2006)
59   !! $ Id: $
60   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt)
61   !!----------------------------------------------------------------------
62
63CONTAINS
64
65   SUBROUTINE sbc_flx( kt )
66      !!---------------------------------------------------------------------
67      !!                    ***  ROUTINE sbc_flx  ***
68      !!                   
69      !! ** Purpose :   provide at each time step the surface ocean fluxes
70      !!                (momentum, heat, freshwater and runoff)
71      !!
72      !! ** Method  : - READ each fluxes in NetCDF files:
73      !!                   i-component of the stress              utau  (N/m2)
74      !!                   j-component of the stress              vtau  (N/m2)
75      !!                   net downward heat flux                 qtot  (watt/m2)
76      !!                   net downward radiative flux            qsr   (watt/m2)
77      !!                   net upward freshwater (evapo - precip) emp   (kg/m2/s)
78      !!                Assumptions made:
79      !!                 - each file content an entire year (read record, not the time axis)
80      !!                 - first and last record are part of the previous and next year
81      !!                   (useful for time interpolation)
82      !!                 - the number of records is 2 + 365*24 / freqh(jf)
83      !!                   or 366 in leap year case
84      !!
85      !!      CAUTION :  - never mask the surface stress fields
86      !!                 - the stress is assumed to be in the mesh referential
87      !!                   i.e. the (i,j) referential
88      !!
89      !! ** Action  :   update at each time-step
90      !!              - utau  & vtau    : stress components in (i,j) referential
91      !!              - qns             : non solar heat flux
92      !!              - qsr             : solar heat flux
93      !!              - emp             : evap - precip (volume flux)
94      !!              - emps            : evap - precip (concentration/dillution)
95      !!----------------------------------------------------------------------
96      INTEGER, INTENT(in) ::   kt   ! ocean time step
97      !!
98      INTEGER  ::   ji, jj, jf   ! dummy indices
99      INTEGER  ::   ierror       ! return error code
100      REAL(wp) ::   zfact        ! temporary scalar
101      REAL(wp) ::   ztx, zty, ztau, zcoef
102      !!
103      CHARACTER(len=100) ::  cn_dir                               ! Root directory for location of flx files
104      TYPE(FLD_N), DIMENSION(jpfld) ::   slf_i                    ! array of namelist information structures
105      TYPE(FLD_N) ::   sn_utau, sn_vtau, sn_qtot, sn_qsr, sn_emp  ! informations about the fields to be read
106      NAMELIST/namsbc_flx/ cn_dir, sn_utau, sn_vtau, sn_qtot, sn_qsr, sn_emp
107      !!---------------------------------------------------------------------
108   INTEGER , PARAMETER ::   jp_utau = 1   ! index of wind stress (i-component) file
109   INTEGER , PARAMETER ::   jp_vtau = 2   ! index of wind stress (j-component) file
110   INTEGER , PARAMETER ::   jp_qtot = 3   ! index of total (non solar+solar) heat file
111   INTEGER , PARAMETER ::   jp_qsr  = 4   ! index of solar heat file
112   INTEGER , PARAMETER ::   jp_emp  = 5   ! index of evaporation-precipation file
113
114
115      !                                         ! ====================== !
116      IF( kt == nit000 ) THEN                   !  First call kt=nit000  !
117         !                                      ! ====================== !
118         ! set file information
119         cn_dir = './'        ! directory in which the model is executed
120         ! ... default values (NB: frequency positive => hours, negative => months)
121         !            !   file    ! frequency !  variable  ! time intep !  clim  ! starting !
122         !            !   name    !  (hours)  !   name     !   (T/F)    !  (0/1) !  record  !
123         sn_utau = FLD_N( 'utau.nc' ,    24.    ,  'utau'    ,  .FALSE.   ,    0   ,     0    )
124         sn_vtau = FLD_N( 'vtau.nc' ,    24.    ,  'vtau'    ,  .FALSE.   ,    0   ,     0    )
125         sn_qtot = FLD_N( 'qtot.nc' ,    24.    ,  'qtot'    ,  .FALSE.   ,    0   ,     0    )
126         sn_qsr  = FLD_N( 'qsr.nc'  ,    24.    ,  'qsr'     ,  .FALSE.   ,    0   ,     0    )
127         sn_emp  = FLD_N( 'emp.nc'  ,    24.    ,  'emp'     ,  .FALSE.   ,    0   ,     0    )
128
129         REWIND ( numnam )               ! ... read in namlist namflx
130         READ   ( numnam, namsbc_flx ) 
131
132         ! store namelist information in an array
133         slf_i(jp_utau) = sn_utau   ;   slf_i(jp_vtau) = sn_vtau
134         slf_i(jp_qtot) = sn_qtot   ;   slf_i(jp_qsr ) = sn_qsr 
135         slf_i(jp_emp ) = sn_emp
136
137         ! set sf structure
138         ALLOCATE( sf(jpfld), STAT=ierror )
139         IF( ierror > 0 ) THEN
140            CALL ctl_stop( 'sbc_flx: unable to allocate sf structure' )   ;   RETURN
141         ENDIF
142
143         DO jf = 1, jpfld
144            WRITE(sf(jf)%clrootname,'(a,a)' )   TRIM( cn_dir ), TRIM( slf_i(jf)%clname )
145            sf(jf)%freqh   = slf_i(jf)%freqh
146            sf(jf)%clvar   = slf_i(jf)%clvar
147            sf(jf)%ln_tint = slf_i(jf)%ln_tint
148            sf(jf)%nclim   = slf_i(jf)%nclim
149            sf(jf)%nstrec  = slf_i(jf)%nstrec
150         END DO
151
152         IF(lwp) THEN      ! control print
153            WRITE(numout,*)
154            WRITE(numout,*) 'sbc_flx : flux formulation for ocean surface boundary condition'
155            WRITE(numout,*) '~~~~~~~ '
156            WRITE(numout,*) '          namsbc_flx Namelist'
157            WRITE(numout,*) '          list of files and frequency (>0: in hours ; <0 in months)'
158            DO jf = 1, jpfld
159                WRITE(numout,*) '               root filename: '  , trim( sf(jf)%clrootname ),   &
160                   &                          ' variable name: '  , trim( sf(jf)%clvar      )
161                WRITE(numout,*) '               frequency: '      ,       sf(jf)%freqh       ,   &
162                   &                          ' time interp: '    ,       sf(jf)%ln_tint     ,   &
163                   &                          ' climatology: '    ,       sf(jf)%nclim       ,   &
164                   &                          ' starting record: ',       sf(jf)%nstrec
165            END DO
166         ENDIF
167         !
168      ENDIF
169
170      CALL fld_read( kt, nn_fsbc, sf )           ! Read input fields and provides the
171      !                                          ! input fields at the current time-step
172
173      ! set the ocean fluxes from read fields
174!CDIR COLLAPSE
175      DO jj = 1, jpj
176         DO ji = 1, jpi
177            utau(ji,jj) = sf(jp_utau)%fnow(ji,jj)
178            vtau(ji,jj) = sf(jp_vtau)%fnow(ji,jj)
179            qns (ji,jj) = sf(jp_qtot)%fnow(ji,jj) - sf(jp_qsr)%fnow(ji,jj)
180            qsr (ji,jj) = sf(jp_qsr )%fnow(ji,jj)
181            emp (ji,jj) = sf(jp_emp )%fnow(ji,jj)
182         END DO
183      END DO
184
185      ! Estimation of wind speed as a function of wind stress ( |tau|=rhoa*Cd*|U|^2 )
186      zcoef = 0.5 / ( rhoa * cdrag ) 
187!CDIR NOVERRCHK
188      DO jj = 2, jpjm1
189!CDIR NOVERRCHK
190         DO ji = fs_2, fs_jpim1   ! vect. opt.
191            ztx = utau(ji-1,jj  ) + utau(ji,jj) 
192            zty = vtau(ji  ,jj-1) + vtau(ji,jj) 
193            ztau = SQRT( ztx * ztx + zty * zty )
194            wndm(ji,jj) = SQRT ( ztau * zcoef ) * tmask(ji,jj,1)
195         END DO
196      END DO
197      CALL lbc_lnk( wndm(:,:) , 'T', 1. )
198
199      ! control print (if less than 100 time-step asked)
200      IF( nitend-nit000 <= 100 .AND. lwp ) THEN
201         WRITE(numout,*) 
202         WRITE(numout,*) '        read daily momentum, heat and freshwater fluxes OK'
203         DO jf = 1, jpfld
204            IF( jf == jp_utau .OR. jf == jp_vtau )   zfact =     1.
205            IF( jf == jp_qtot .OR. jf == jp_qsr  )   zfact =     0.1
206            IF( jf == jp_emp                     )   zfact = 86400.
207            WRITE(numout,*) 
208            WRITE(numout,*) ' day: ', ndastp , TRIM(sf(jf)%clvar), ' * ', zfact
209            CALL prihre( sf(jf)%fnow, jpi, jpj, 1, jpi, 20, 1, jpj, 10, 1., numout )
210         END DO
211         CALL FLUSH(numout)
212      ENDIF
213      !
214   END SUBROUTINE sbc_flx
215
216   !!======================================================================
217END MODULE sbcflx
Note: See TracBrowser for help on using the repository browser.