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 @ 1029

Last change on this file since 1029 was 1029, checked in by cetlod, 16 years ago

adding wind speed module variable, see ticket 172

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