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

source: trunk/NEMO/OPA_SRC/TRA/traqsr.F90 @ 531

Last change on this file since 531 was 503, checked in by opalod, 18 years ago

nemo_v1_update_064 : CT : general trends update including the addition of mean windows analysis possibility in the mixed layer

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 12.8 KB
Line 
1MODULE traqsr
2   !!======================================================================
3   !!                       ***  MODULE  traqsr  ***
4   !! Ocean physics: solar radiation penetration in the top ocean levels
5   !!======================================================================
6   !! History :  6.0  !  90-10  (B. Blanke)  Original code
7   !!            7.0  !  91-11  (G. Madec)
8   !!                 !  96-01  (G. Madec)  s-coordinates
9   !!            8.5  !  02-06  (G. Madec)  F90: Free form and module
10   !!            9.0  !  05-11  (G. Madec) zco, zps, sco coordinate
11   !!----------------------------------------------------------------------
12
13   !!----------------------------------------------------------------------
14   !!   tra_qsr      : trend due to the solar radiation penetration
15   !!   tra_qsr_init : solar radiation penetration initialization
16   !!----------------------------------------------------------------------
17   USE oce             ! ocean dynamics and active tracers
18   USE dom_oce         ! ocean space and time domain
19   USE trdmod          ! ocean active tracers trends
20   USE trdmod_oce      ! ocean variables trends
21   USE in_out_manager  ! I/O manager
22   USE trc_oce         ! share SMS/Ocean variables
23   USE ocesbc          ! thermohaline fluxes
24   USE phycst          ! physical constants
25   USE prtctl          ! Print control
26
27   IMPLICIT NONE
28   PRIVATE
29
30   PUBLIC   tra_qsr      ! routine called by step.F90 (ln_traqsr=T)
31   PUBLIC   tra_qsr_init ! routine called by opa.F90
32
33   !!* Namelist namqsr: penetrative solar radiation
34   LOGICAL , PUBLIC ::   ln_traqsr = .TRUE.   !: qsr flag (Default=T)
35   REAL(wp), PUBLIC ::   rabs = 0.58_wp       ! fraction associated with xsi1
36   REAL(wp), PUBLIC ::   xsi1 = 0.35_wp       ! first depth of extinction
37   REAL(wp), PUBLIC ::   xsi2 = 23.0_wp       ! second depth of extinction (default values: water type Ib)
38   LOGICAL , PUBLIC ::   ln_qsr_sms = .false. ! flag to use or not the biological fluxes for light
39   NAMELIST/namqsr/ ln_traqsr, rabs, xsi1, xsi2, ln_qsr_sms
40   
41   INTEGER ::   nksr   ! number of levels
42   REAL(wp), DIMENSION(jpk) ::   gdsr   ! profile of the solar flux penetration
43
44   !! * Substitutions
45#  include "domzgr_substitute.h90"
46#  include "vectopt_loop_substitute.h90"
47   !!----------------------------------------------------------------------
48   !!   OPA 9.0 , LOCEAN-IPSL (2005)
49   !! $Header$
50   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt)
51   !!----------------------------------------------------------------------
52
53CONTAINS
54
55   SUBROUTINE tra_qsr( kt )
56      !!----------------------------------------------------------------------
57      !!                  ***  ROUTINE tra_qsr  ***
58      !!
59      !! ** Purpose :   Compute the temperature trend due to the solar radiation
60      !!      penetration and add it to the general temperature trend.
61      !!
62      !! ** Method  : The profile of the solar radiation within the ocean is
63      !!      defined through two penetration length scale (xsr1,xsr2) and a
64      !!      ratio (rabs) as :
65      !!         I(k) = Qsr*( rabs*EXP(z(k)/xsr1) + (1.-rabs)*EXP(z(k)/xsr2) )
66      !!         The temperature trend associated with the solar radiation
67      !!      penetration is given by :
68      !!            zta = 1/e3t dk[ I ] / (rau0*Cp)
69      !!         At the bottom, boudary condition for the radiation is no flux :
70      !!      all heat which has not been absorbed in the above levels is put
71      !!      in the last ocean level.
72      !!         In z-coordinate case, the computation is only done down to the
73      !!      level where I(k) < 1.e-15 W/m2. In addition, the coefficients
74      !!      used for the computation are calculated one for once as they
75      !!      depends on k only.
76      !!
77      !! ** Action  : - update ta with the penetrative solar radiation trend
78      !!              - save the trend in ttrd ('key_trdtra')
79      !!----------------------------------------------------------------------
80      USE oce, ONLY :   ztrdt => ua   ! use ua as 3D workspace   
81      USE oce, ONLY :   ztrds => va   ! use va as 3D workspace   
82      !!
83      INTEGER, INTENT(in) ::   kt     ! ocean time-step
84      !!
85      INTEGER  ::    ji, jj, jk       ! dummy loop indexes
86      REAL(wp) ::   zc0 , zta         ! temporary scalars
87      !!----------------------------------------------------------------------
88
89      IF( kt == nit000 ) THEN
90         IF(lwp) WRITE(numout,*)
91         IF(lwp) WRITE(numout,*) 'tra_qsr : penetration of the surface solar radiation'
92         IF(lwp) WRITE(numout,*) '~~~~~~~'
93         CALL tra_qsr_init
94      ENDIF
95
96      IF( l_trdtra ) THEN      ! Save ta and sa trends
97         ztrdt(:,:,:) = ta(:,:,:) 
98         ztrds(:,:,:) = 0.e0
99      ENDIF
100
101      ! ---------------------------------------------- !
102      !  Biological fluxes  : all vertical coordinate  !
103      ! ---------------------------------------------- !
104      IF( lk_qsr_sms .AND. ln_qsr_sms ) THEN     
105         !                                                   ! ===============
106         DO jk = 1, jpkm1                                    ! Horizontal slab
107            !                                                ! ===============
108            DO jj = 2, jpjm1
109               DO ji = fs_2, fs_jpim1   ! vector opt.
110                  zc0 = ro0cpr  / fse3t(ji,jj,jk)         ! compute the qsr trend
111                  zta = zc0 * ( etot3(ji,jj,jk  ) * tmask(ji,jj,jk)     &
112                     &        - etot3(ji,jj,jk+1) * tmask(ji,jj,jk+1) )
113                  ta(ji,jj,jk) = ta(ji,jj,jk) + zta       ! add qsr trend to the temperature trend
114               END DO
115            END DO
116            !                                                ! ===============
117         END DO                                              !   End of slab
118         !                                                   ! ===============
119
120      ! ---------------------------------------------- !
121      !  Ocean alone :
122      ! ---------------------------------------------- !
123      ELSE
124         !                                                ! =================== !
125         IF( ln_sco ) THEN                                !    s-coordinate     !
126            !                                             ! =================== !
127            DO jk = 1, jpkm1
128               ta(:,:,jk) = ta(:,:,jk) + etot3(:,:,jk) * qsr(:,:)
129            END DO
130         ENDIF
131         !                                                ! =================== !
132         IF( ln_zps ) THEN                                !    partial steps    !
133            !                                             ! =================== !
134            DO jk = 1, nksr
135               DO jj = 2, jpjm1
136                  DO ji = fs_2, fs_jpim1   ! vector opt.
137                     ! qsr trend from gdsr
138                     zc0 = qsr(ji,jj) / fse3t(ji,jj,jk)
139                     zta = zc0 * ( gdsr(jk) * tmask(ji,jj,jk) - gdsr(jk+1) * tmask(ji,jj,jk+1) )
140                     ! add qsr trend to the temperature trend
141                     ta(ji,jj,jk) = ta(ji,jj,jk) + zta
142                  END DO
143               END DO
144            END DO
145         ENDIF
146         !                                                ! =================== !
147         IF( ln_zco ) THEN                                !     z-coordinate    !
148            !                                             ! =================== !
149            DO jk = 1, nksr
150               zc0 = 1. / e3t_0(jk)
151               DO jj = 2, jpjm1
152                  DO ji = fs_2, fs_jpim1   ! vector opt.
153                     ! qsr trend
154                     zta = qsr(ji,jj) * zc0 * ( gdsr(jk)*tmask(ji,jj,jk) - gdsr(jk+1)*tmask(ji,jj,jk+1) )
155                     ! add qsr trend to the temperature trend
156                     ta(ji,jj,jk) = ta(ji,jj,jk) + zta     
157                  END DO
158               END DO
159            END DO
160         ENDIF
161         !
162      ENDIF
163
164      IF( l_trdtra ) THEN     ! qsr tracers trends saved for diagnostics
165         ztrdt(:,:,:) = ta(:,:,:) - ztrdt(:,:,:)
166         CALL trd_mod( ztrdt, ztrds, jptra_trd_qsr, 'TRA', kt )
167      ENDIF
168      !                       ! print mean trends (used for debugging)
169      IF(ln_ctl)   CALL prt_ctl( tab3d_1=ta, clinfo1=' qsr  - Ta: ', mask1=tmask, clinfo3='tra-ta' )
170      !
171   END SUBROUTINE tra_qsr
172
173
174   SUBROUTINE tra_qsr_init
175      !!----------------------------------------------------------------------
176      !!                  ***  ROUTINE tra_qsr_init  ***
177      !!
178      !! ** Purpose :   Initialization for the penetrative solar radiation
179      !!
180      !! ** Method  :   The profile of solar radiation within the ocean is set
181      !!      from two length scale of penetration (xsr1,xsr2) and a ratio
182      !!      (rabs). These parameters are read in the namqsr namelist. The
183      !!      default values correspond to clear water (type I in Jerlov'
184      !!      (1968) classification.
185      !!         called by tra_qsr at the first timestep (nit000)
186      !!
187      !! ** Action  : - initialize xsr1, xsr2 and rabs
188      !!
189      !! Reference : Jerlov, N. G., 1968 Optical Oceanography, Elsevier, 194pp.
190      !!----------------------------------------------------------------------
191      INTEGER  ::   ji, jj, jk   ! dummy loop index
192      INTEGER  ::   indic        ! temporary integer
193      REAL(wp) ::   zc0 , zc1 , zc2    ! temporary scalars
194      REAL(wp) ::   zcst, zdp1, zdp2   !    "         "
195      !!----------------------------------------------------------------------
196
197      REWIND ( numnam )           ! Read Namelist namqsr : ratio and length of penetration
198      READ   ( numnam, namqsr )
199
200      IF( ln_traqsr  ) THEN       ! Parameter control and print
201         IF(lwp) THEN
202            WRITE(numout,*)
203            WRITE(numout,*) 'tra_qsr_init : penetration of the surface solar radiation'
204            WRITE(numout,*) '~~~~~~~~~~~~'
205            WRITE(numout,*) '    Namelist namqsr : set the parameter of penetration'
206            WRITE(numout,*) '        fraction associated with xsi     rabs        = ',rabs
207            WRITE(numout,*) '        first depth of extinction        xsi1        = ',xsi1
208            WRITE(numout,*) '        second depth of extinction       xsi2        = ',xsi2
209            IF( lk_qsr_sms ) THEN
210               WRITE(numout,*) '     Biological fluxes for light(Y/N) ln_qsr_sms  = ',ln_qsr_sms
211            ENDIF
212         ENDIF
213      ELSE
214         IF(lwp) THEN
215            WRITE(numout,*)
216            WRITE(numout,*) 'tra_qsr_init : NO solar flux penetration'
217            WRITE(numout,*) '~~~~~~~~~~~~'
218         ENDIF
219      ENDIF
220
221      IF( rabs > 1.e0 .OR. rabs < 0.e0 .OR. xsi1 < 0.e0 .OR. xsi2 < 0.e0 ) &
222         CALL ctl_stop( '             0<rabs<1, 0<xsi1, or 0<xsi2 not satisfied' )
223
224      !                           ! Initialization of gdsr
225      IF( ln_zco .OR. ln_zps ) THEN
226         !
227         ! z-coordinate with or without partial step : same w-level everywhere inside the ocean
228         gdsr(:) = 0.e0
229         DO jk = 1, jpk
230            zdp1 = -gdepw_0(jk)
231            gdsr(jk) = ro0cpr * (  rabs  * EXP( zdp1/xsi1 ) + (1.-rabs) * EXP( zdp1/xsi2 )  )
232            IF ( gdsr(jk) <= 1.e-10 ) EXIT
233         END DO
234         indic = 0
235         DO jk = 1, jpk
236            IF( gdsr(jk) <= 1.e-15 .AND. indic == 0 ) THEN
237               gdsr(jk) = 0.e0
238               nksr = jk
239               indic = 1
240            ENDIF
241         END DO
242         nksr = MIN( nksr, jpkm1 )
243         IF(lwp) THEN
244            WRITE(numout,*)
245            WRITE(numout,*) '        - z-coordinate, level max of computation =', nksr
246            WRITE(numout,*) '             profile of coef. of penetration:'
247            WRITE(numout,"('              ',7e11.2)") ( gdsr(jk), jk = 1, nksr )
248            WRITE(numout,*)
249         ENDIF
250         ! Initialisation of Biological fluxes for light here because
251         ! the optical biological model is call after the dynamical one
252         IF( lk_qsr_sms .AND. ln_qsr_sms ) THEN
253            DO jk = 1, jpkm1
254               zcst = gdsr(jk) / ro0cpr
255               etot3(:,:,jk) = qsr(:,:) * zcst * tmask(:,:,jk) 
256            END DO
257         ENDIF
258         !
259      ENDIF
260
261      ! Initialisation of etot3 (s-coordinate)
262      ! -----------------------
263      IF( ln_sco ) THEN
264         etot3(:,:,jpk) = 0.e0
265         DO jk = 1, jpkm1
266            DO jj = 1, jpj
267               DO ji = 1, jpi
268                  zdp1 = -fsdepw(ji,jj,jk  )
269                  zdp2 = -fsdepw(ji,jj,jk+1)
270                  zc0  = ro0cpr / fse3t(ji,jj,jk)
271                  zc1  =   (  rabs * EXP(zdp1/xsi1) + (1.-rabs) * EXP(zdp1/xsi2)  )
272                  zc2  = - (  rabs * EXP(zdp2/xsi1) + (1.-rabs) * EXP(zdp2/xsi2)  )
273                  etot3(ji,jj,jk)  = zc0 * (  zc1 * tmask(ji,jj,jk) + zc2 * tmask(ji,jj,jk+1)  )
274               END DO
275            END DO
276         END DO
277      ENDIF
278      !
279   END SUBROUTINE tra_qsr_init
280
281   !!======================================================================
282END MODULE traqsr
Note: See TracBrowser for help on using the repository browser.