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.
sbcblk_clio.F90 in trunk/NEMO/OPA_SRC/SBC – NEMO

source: trunk/NEMO/OPA_SRC/SBC/sbcblk_clio.F90 @ 702

Last change on this file since 702 was 702, checked in by smasson, 17 years ago

add first set of new surface module, see ticket:3

  • Property svn:executable set to *
File size: 13.2 KB
Line 
1MODULE sbcblk_clio
2   !!======================================================================
3   !!                       ***  MODULE  sbcblk_clio  ***
4   !! Ocean forcing:  momentum, heat and freshwater flux formulation
5   !!=====================================================================
6   !! History :  8.0  !  01-04  (Louvain-La-Neuve)  Original code
7   !!            8.5  !  02-09  (C. Ethe , G. Madec )  F90: Free form and module
8   !!            9.0  !  06-06  (G. Madec)  surface module
9   !!----------------------------------------------------------------------
10   
11   !!----------------------------------------------------------------------
12   !!   sbc_blk_clio  : bulk formulation as ocean surface boundary condition
13   !!                   (forced mode, CORE bulk formulea)
14   !!   blk_oce_clio  : ocean: computes momentum, heat and freshwater fluxes
15   !!   blk_ice_clio  : ice  : computes momentum, heat and freshwater fluxes
16   !!----------------------------------------------------------------------
17   !!   flx_blk_declin : Computation of the solar declination
18   !!----------------------------------------------------------------------
19   USE oce             ! ocean dynamics and tracers
20   USE dom_oce         ! ocean space and time domain
21   USE cpl_oce         ! ???
22   USE phycst          ! physical constants
23   USE daymod
24
25   USE sbc_oce         ! Surface boundary condition: ocean fields
26   USE sbc_ice         ! Surface boundary condition: ocean fields
27
28   USE fldread         ! read input fields
29
30   USE ocfzpt          ! ???
31
32   USE iom
33   USE in_out_manager
34   USE lbclnk
35   USE prtctl          ! Print control
36
37   IMPLICIT NONE
38   PRIVATE
39
40   PUBLIC   sbc_blk_clio   ! routine called in sbcmod
41   PUBLIC   blk_ice_clio   ! routine called in sbcice_lim module
42
43   INTEGER , PARAMETER ::    &
44      jpfld   = 7,     &  ! number of files to read
45      jp_utau = 1,     &  ! index of wind stress (i-component)  (m/s)    at U-point
46      jp_vtau = 2,     &  ! index of wind stress (j-component)  (m/s)    at V-point
47      jp_wspd = 3,     &  ! index of XXm wind module            (m/s)    at T-point
48      jp_tair = 4,     &  ! index of  2m air temperature        (Celcius)
49      jp_humi = 5,     &  ! index of specific humidity          ( % )
50      jp_cldc = 6,     &  ! Cloud cover                       ( % )
51      jp_prec = 7         ! index of total precipitation        (kg/m2/s)
52   TYPE(FLD), ALLOCATABLE, DIMENSION(:) ::   sf   ! structure of input fields (informations on files, fields read)
53
54   !! * CLIO bulk parameters
55   INTEGER, PARAMETER  ::   jpintsr = 24          ! number of time step between sunrise and sunset
56      !                                           ! uses for heat flux computation
57   LOGICAL             ::   lbulk_init = .TRUE.   ! flag, bulk initialization done or not)
58     
59   REAL(wp), DIMENSION(jpi,jpj) ::   stauc        ! cloud optical depth
60   REAL(wp), DIMENSION(jpi,jpj) ::   sbudyko      ! ???
61     
62   !! * constants for bulk computation (flx_blk)
63   REAL(wp), DIMENSION(19)  ::  budyko            ! BUDYKO's coefficient
64   !                                              ! BUDYKO's coefficient (cloudiness effect on LW radiation):
65   DATA budyko / 1.00, 0.98, 0.95, 0.92, 0.89, 0.86, 0.83, 0.80, 0.78, 0.75,  &
66      &          0.72, 0.69, 0.67, 0.64, 0.61, 0.58, 0.56, 0.53, 0.50 /
67   REAL(wp), DIMENSION(20)  ::   tauco            ! cloud optical depth coefficient
68   !                                              ! Cloud optical depth coefficient
69   DATA tauco / 6.6, 6.6, 7.0, 7.2, 7.1, 6.8, 6.5, 6.6, 7.1, 7.6,   &
70      &         6.6, 6.1, 5.6, 5.5, 5.8, 5.8, 5.6, 5.6, 5.6, 5.6 /
71
72   REAL(wp) ::   zeps    = 1.e-20  ,  &  ! constant values
73      &          zeps0   = 1.e-13  ,  &
74      &          zeps1   = 1.e-06  ,  &
75      &          zzero   = 0.e0    ,  &
76      &          zone    = 1.0
77
78   REAL(wp) ::   yearday   !
79
80   !!----------------------------------------------------------------------
81   !!   OPA 9.0 , LOCEAN-IPSL (2006)
82   !! $Header: $
83   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt)
84   !!----------------------------------------------------------------------
85
86CONTAINS
87
88   SUBROUTINE sbc_blk_clio( kt )
89      !!---------------------------------------------------------------------
90      !!                    ***  ROUTINE sbc_blk_clio  ***
91      !!
92      !! ** Purpose :   provide at each time step the surface ocean fluxes
93      !!      (momentum, heat, freshwater and runoff)
94      !!
95      !! ** Method  :   READ each fluxes in NetCDF files
96      !!      The i-component of the stress                taux   (N/m2)
97      !!      The j-component of the stress                tauy   (N/m2)
98      !!      the net downward heat flux                   qtot   (watt/m2)
99      !!      the net downward radiative flux              qsr    (watt/m2)
100      !!      the net upward water (evapo - precip)        emp    (kg/m2/s)
101      !!                Assumptions made:
102      !!       - each file content an entire year (read record, not the time axis)
103      !!       - first and last record are part of the previous and next year
104      !!         (useful for time interpolation)
105      !!       - the number of records is 2 + 365*24 / freqh(jf)
106      !!         or 366 in leap year case
107      !!
108      !!      C A U T I O N : never mask the surface stress fields
109      !!                      the stress is assumed to be in the mesh referential
110      !!                      i.e. the (i,j) referential
111      !!
112      !! ** Action  :   defined at each time-step at the air-sea interface
113      !!              - utau  &  vtau   : stress components in geographical ref.
114      !!              - qns   &  qsr    : non solar and solar heat fluxes
115      !!              - emp             : evap - precip (volume flux)
116      !!              - emps            : evap - precip (concentration/dillution)
117      !!----------------------------------------------------------------------
118      INTEGER, INTENT( in  ) ::   kt   ! ocean time step
119      !!
120      INTEGER  ::   jf                  ! dummy indices
121      INTEGER  ::   ierror   ! return error code
122      !!
123      CHARACTER(len=100) ::  cn_dir   !   Root directory for location of clio files
124      TYPE(FLD_N), DIMENSION(jpfld) ::   slf_i         ! array of namelist informations on the fields to read
125      TYPE(FLD_N) ::   sn_utau, sn_vtau, sn_wspd, sn_tair,  &  ! informations about the fields to be read
126         &             sn_humi, sn_cldc, sn_prec
127      NAMELIST/namsbc_clio/ cn_dir, sn_utau, sn_vtau, sn_wspd, sn_tair,   &
128         &                          sn_humi, sn_cldc, sn_prec
129      !!---------------------------------------------------------------------
130
131      !                                         ! ====================== !
132      IF( kt == nit000 ) THEN                   !  First call kt=nit000  !
133         !                                      ! ====================== !
134         ! set file information (default values)
135         cn_dir = './'       ! directory in which the model is executed
136         ! (NB: frequency positive => hours, negative => months)
137         !              !  file  ! frequency !  variable  ! time intep !  clim  ! starting !
138         !              !  name  !  (hours)  !   name     !   (T/F)    !  (0/1) !  record  !
139         sn_utau = FLD_N( 'utau' ,    24.    , 'utau'     ,  .FALSE.   ,    0   ,    0     )
140         sn_vtau = FLD_N( 'vtau' ,    24.    , 'vtau'     ,  .FALSE.   ,    0   ,    0     )
141         sn_wspd = FLD_N( 'wspd' ,    24.    , 'wspd'     ,  .FALSE.   ,    0   ,    0     )
142         sn_tair = FLD_N( 'tair' ,    24.    , 'Tair'     ,  .FALSE.   ,    0   ,    0     )
143         sn_humi = FLD_N( 'humi' ,   -12.    , 'humi'     ,  .FALSE.   ,    0   ,    0     )
144         sn_cldc = FLD_N( 'cloud',   -12.    , 'cloud'    ,  .FALSE.   ,    0   ,    0     )
145         sn_prec = FLD_N( 'rain' ,   -12.    , 'precip'   ,  .FALSE.   ,    0   ,    0     )
146
147         REWIND ( numnam )                    ! ... read in namlist namsbc_clio
148         READ   ( numnam, namsbc_clio )
149
150         ! store namelist information in an array
151         slf_i(jp_utau) = sn_utau   ;   slf_i(jp_vtau) = sn_vtau
152         slf_i(jp_wspd) = sn_wspd   ;   slf_i(jp_tair) = sn_tair
153         slf_i(jp_humi) = sn_humi   ;   slf_i(jp_cldc) = sn_cldc
154         slf_i(jp_prec) = sn_prec
155
156         ! set sf structure
157         ALLOCATE( sf(jpfld), STAT=ierror )
158         IF( ierror > 0 ) THEN
159            CALL ctl_stop( 'sbc_blk_clio: unable to allocate sf_sst structure' )   ;   RETURN
160         ENDIF
161
162         DO jf = 1, jpfld
163            WRITE(sf(jf)%clrootname,'(a,a)' )   TRIM( cn_dir ), TRIM( slf_i(jf)%clname )
164            sf(jf)%freqh   = slf_i(jf)%freqh
165            sf(jf)%clvar   = slf_i(jf)%clvar
166            sf(jf)%ln_tint = slf_i(jf)%ln_tint
167            sf(jf)%nclim   = slf_i(jf)%nclim
168            sf(jf)%nstrec  = slf_i(jf)%nstrec
169         END DO
170
171         IF(lwp) THEN      ! control print
172            WRITE(numout,*)
173            WRITE(numout,*) 'sbc_blk_clio : CLIO bulk formulation for ocean surface boundary condition'
174            WRITE(numout,*) '~~~~~~~~~~~~ '
175            WRITE(numout,*) '          namsbc_clio Namelist'
176            WRITE(numout,*) '          list of files and frequency (>0: in hours ; <0 in months)'
177            DO jf = 1, jpfld
178                WRITE(numout,*) '               root filename: '  , trim( sf(jf)%clrootname ),   &
179                   &                          ' variable name: '  , trim( sf(jf)%clvar      )
180                WRITE(numout,*) '               frequency: '      ,       sf(jf)%freqh       ,   &
181                   &                          ' time interp: '    ,       sf(jf)%ln_tint     ,   &
182                   &                          ' climatology: '    ,       sf(jf)%nclim       ,   &
183                   &                          ' starting record: ',       sf(jf)%nstrec
184            END DO
185         ENDIF
186         !
187      ENDIF
188
189      CALL fld_read( kt, nn_fsbc, sf )           ! Read input fields and provides the
190      !                                          ! input fields at the current time-step
191!CDIR COLLAPSE
192      utau(:,:) = sf(jp_utau)%fnow(:,:)          ! set surface ocean stresses directly
193!CDIR COLLAPSE
194      vtau(:,:) = sf(jp_vtau)%fnow(:,:)          ! from the input values
195
196      CALL blk_oce_clio( )                       ! set the ocean surface heat and freshwater fluxes
197      !                                          ! using CLIO bulk formulea
198
199! temporary staff : set fluxes to zero....
200      qns (:,:)= 0.e0
201      qsr (:,:)= 0.e0
202      emp (:,:)= 0.e0
203      emps(:,:)= 0.e0
204
205      ! control print (if less than 100 time-step asked)
206!!!   IF( nitend-nit000 <= 100 .AND. lwp ) THEN
207      IF( kt == nit000 .AND. lwp ) THEN
208         WRITE(numout,*)
209         WRITE(numout,*) '        CLIO bulk fields at nit000'
210         DO jf = 1, jpfld
211            WRITE(numout,*)
212            WRITE(numout,*) ' day: ', ndastp , TRIM(sf(jf)%clvar)
213            CALL prihre( sf(jf)%fnow, jpi, jpj, 1, jpi, 20, 1, jpj, 10, 1., numout )
214         END DO
215         CALL FLUSH(numout)
216      ENDIF
217
218   END SUBROUTINE sbc_blk_clio
219
220
221   SUBROUTINE blk_oce_clio( )
222   END SUBROUTINE blk_oce_clio
223
224
225   SUBROUTINE blk_ice_clio
226   END SUBROUTINE blk_ice_clio
227
228
229   SUBROUTINE blk_qsr_clio( )
230   END SUBROUTINE blk_qsr_clio
231
232
233   SUBROUTINE flx_blk_declin( ky, kday, pdecl )
234      !!---------------------------------------------------------------------------
235      !!               ***  ROUTINE flx_blk_declin  ***
236      !!         
237      !! ** Purpose :   Computation of the solar declination for the day
238      !!         kday ( in decimal degrees ).
239      !!       
240      !! ** Method  :
241      !!---------------------------------------------------------------------
242      INTEGER , INTENT(in   ) ::   ky      ! = -1, 0, 1 for odd, normal and leap years resp.
243      INTEGER , INTENT(in   ) ::   kday    ! day of the year ( kday = 1 on january 1)
244      REAL(wp), INTENT(  out) ::   pdecl   ! solar declination
245
246      REAL(wp) ::   zday              ,  &  ! corresponding day of type year (cf. ky)
247         &          zp1, zp2, zp3, zp4      ! temporary scalars
248      REAL(wp) ::   a0  =  0.39507671 ,  &  ! constants used in  solar
249         &          a1  = 22.85684301 ,  &  ! declinaison computation
250         &          a2  = -0.38637317 ,  &
251         &          a3  =  0.15096535 ,  &
252         &          a4  = -0.00961411 ,  &
253         &          b1  = -4.29692073 ,  &
254         &          b2  =  0.05702074 ,  &
255         &          b3  = -0.09028607 ,  &
256         &          b4  =  0.00592797
257      !!---------------------------------------------------------------------
258      !
259      SELECT CASE ( ky )
260      CASE ( 1 )
261         zday = REAL( kday, wp ) - 0.5
262      CASE ( 3 )
263         zday = REAL( kday, wp ) - 1.0
264      CASE DEFAULT
265         zday = REAL( kday, wp ) 
266      END SELECT
267           
268      zp1 = rpi * ( 2.0 * zday - 367.0 ) / yearday
269      zp2 = 2. * zp1
270      zp3 = 3. * zp1
271      zp4 = 4. * zp1
272     
273      pdecl  = a0                                                                      &
274         &   + a1 * COS( zp1 ) + a2 * COS( zp2 ) + a3 * COS( zp3 ) + a4 * COS( zp4 )   &
275         &   + b1 * SIN( zp1 ) + b2 * SIN( zp2 ) + b3 * SIN( zp3 ) + b4 * SIN( zp4 )
276      !
277   END SUBROUTINE flx_blk_declin
278
279   !!======================================================================
280END MODULE sbcblk_clio
Note: See TracBrowser for help on using the repository browser.