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

Last change on this file since 719 was 719, checked in by ctlod, 17 years ago

get back to the nemo_v2_3 version for trunk

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