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.
trc_oce.F90 in branches/UKMO/dev_r5518_AMM15_package/NEMOGCM/NEMO/OPA_SRC – NEMO

source: branches/UKMO/dev_r5518_AMM15_package/NEMOGCM/NEMO/OPA_SRC/trc_oce.F90 @ 10253

Last change on this file since 10253 was 10253, checked in by kingr, 5 years ago

Merged AMM15_v3_6_STABLE_package_collate@10237

File size: 18.0 KB
Line 
1MODULE trc_oce
2   !!======================================================================
3   !!                      ***  MODULE  trc_oce  ***
4   !! Ocean passive tracer  :  share SMS/Ocean variables
5   !!======================================================================
6   !! History :  1.0  !  2004-03  (C. Ethe)  Original code
7   !!----------------------------------------------------------------------
8
9   !!----------------------------------------------------------------------
10   !!   trc_oce_rgb : tabulated attenuation coefficients for RGB light penetration         
11   !!----------------------------------------------------------------------
12   USE par_oce
13   USE in_out_manager  ! I/O manager
14   USE dom_oce         ! ocean space and time domain
15   USE lib_mpp         ! MPP library
16
17   IMPLICIT NONE
18   PRIVATE
19
20   PUBLIC   trc_oce_rgb        ! routine called by traqsr.F90
21   PUBLIC   trc_oce_rgb_read   ! routine called by traqsr.F90
22   PUBLIC   trc_oce_ext_lev    ! function called by traqsr.F90 at least
23   PUBLIC   trc_oce_alloc      ! function called by nemogcm.F90
24
25   INTEGER , PUBLIC                                      ::   nn_dttrc      !: frequency of step on passive tracers
26   REAL(wp), PUBLIC                                      ::   r_si2         !: largest depth of extinction (blue & 0.01 mg.m-3)  (RGB)
27   REAL(wp), PUBLIC, SAVE, ALLOCATABLE, DIMENSION(:,:,:) ::   etot3         !: light absortion coefficient
28   REAL(wp), PUBLIC, SAVE, ALLOCATABLE, DIMENSION(:,:,:) ::   facvol        !: volume for degraded regions
29   REAL(wp), PUBLIC, SAVE, ALLOCATABLE, DIMENSION(:,:)   ::   rlambda2      !: Lambda2 for downwell version of Short wave Radiation
30   REAL(wp), PUBLIC                                      ::   rlambda       !: Lambda  for downwell version of Short wave Radiation
31
32#if defined key_top 
33   !!----------------------------------------------------------------------
34   !!   'key_top'                                                 bio-model         
35   !!----------------------------------------------------------------------
36   LOGICAL, PUBLIC, PARAMETER ::   lk_top     = .TRUE.   !: TOP model
37   LOGICAL, PUBLIC, PARAMETER ::   lk_qsr_bio = .TRUE.   !: bio-model light absorption flag
38#else
39   !!----------------------------------------------------------------------
40   !! Default option                          No bio-model light absorption     
41   !!----------------------------------------------------------------------
42   LOGICAL, PUBLIC, PARAMETER ::   lk_top     = .FALSE.   !: TOP model
43   LOGICAL, PUBLIC, PARAMETER ::   lk_qsr_bio = .FALSE.   !: bio-model light absorption flag
44#endif
45
46#if defined key_offline
47   !!----------------------------------------------------------------------
48   !!   'key_offline'                                     OFFLINE mode         
49   !!----------------------------------------------------------------------
50   LOGICAL, PUBLIC, PARAMETER ::   lk_offline = .TRUE.   !: offline flag
51#else
52   !!----------------------------------------------------------------------
53   !!   Default option                                   NO  OFFLINE mode         
54   !!----------------------------------------------------------------------
55   LOGICAL, PUBLIC, PARAMETER ::   lk_offline = .FALSE.   !: offline flag
56#endif
57#if defined key_degrad
58   !!----------------------------------------------------------------------
59   !!   'key_degrad'                                     Degradation mode         
60   !!----------------------------------------------------------------------
61   LOGICAL, PUBLIC, PARAMETER ::   lk_degrad = .TRUE.   !: degradation flag
62#else
63   !!----------------------------------------------------------------------
64   !!   Default option                                   NO  Degradation mode         
65   !!----------------------------------------------------------------------
66   LOGICAL, PUBLIC, PARAMETER ::   lk_degrad = .FALSE.   !: degradation flag
67#endif
68
69   !! * Substitutions
70#  include "domzgr_substitute.h90"
71   !!----------------------------------------------------------------------
72   !! NEMO/OPA 3.3 , NEMO Consortium (2010)
73   !! $Id$
74   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
75   !!----------------------------------------------------------------------
76CONTAINS
77
78   INTEGER FUNCTION trc_oce_alloc()
79      !!----------------------------------------------------------------------
80      !!                  ***  trc_oce_alloc  ***
81      !!----------------------------------------------------------------------
82      INTEGER ::   ierr(3)        ! Local variables
83      !!----------------------------------------------------------------------
84      ierr(:) = 0
85                     ALLOCATE( etot3 (jpi,jpj,jpk), STAT=ierr(1) )
86      IF( lk_degrad) ALLOCATE( facvol(jpi,jpj,jpk), STAT=ierr(2) )
87                    ALLOCATE( rlambda2(jpi,jpj),   STAT=ierr(3) )
88      trc_oce_alloc  = MAXVAL( ierr )
89      !
90      IF( trc_oce_alloc /= 0 )   CALL ctl_warn('trc_oce_alloc: failed to allocate etot3 array')
91      IF( trc_oce_alloc /= 0 )   CALL ctl_warn('trc_oce_alloc: failed to allocate etot3, facvol or rlambda2 array')
92   END FUNCTION trc_oce_alloc
93
94
95   SUBROUTINE trc_oce_rgb( prgb )
96      !!---------------------------------------------------------------------
97      !!                  ***  ROUTINE p4z_opt_init  ***
98      !!
99      !! ** Purpose :   Initialization of of the optical scheme
100      !!
101      !! ** Method  :   Set a look up table for the optical coefficients
102      !!                i.e. the attenuation coefficient for R-G-B light
103      !!                tabulated in Chlorophyll class (from JM Andre)
104      !!
105      !! ** Action  :   prgb(3,61) tabulated R-G-B attenuation coef.
106      !!
107      !! Reference  : Lengaigne et al. 2007, Clim. Dyn., V28, 5, 503-516.
108      !!----------------------------------------------------------------------
109      REAL(wp), DIMENSION(3,61), INTENT(out) ::   prgb   ! tabulated attenuation coefficient
110      !!
111      INTEGER  ::   jc     ! dummy loop indice
112      INTEGER  ::   irgb   ! temporary integer
113      REAL(wp) ::   zchl   ! temporary scalar
114      REAL(wp), DIMENSION(4,61) ::   zrgb   ! tabulated attenuation coefficient (formerly read in 'kRGB61.txt')
115      !!----------------------------------------------------------------------
116      !
117      IF(lwp) THEN
118         WRITE(numout,*)
119         WRITE(numout,*) 'trc_oce_rgb : Initialisation of the optical look-up table'
120         WRITE(numout,*) '~~~~~~~~~~~ '
121      ENDIF
122      !
123      !  Chlorophyll        !     Blue attenuation     !     Green attenuation    !     Red attenuation      !
124      zrgb(1, 1) =  0.010   ;   zrgb(2, 1) = 0.01618   ;   zrgb(3, 1) = 0.07464   ;   zrgb(4, 1) = 0.37807
125      zrgb(1, 2) =  0.011   ;   zrgb(2, 2) = 0.01654   ;   zrgb(3, 2) = 0.07480   ;   zrgb(4, 2) = 0.37823
126      zrgb(1, 3) =  0.013   ;   zrgb(2, 3) = 0.01693   ;   zrgb(3, 3) = 0.07499   ;   zrgb(4, 3) = 0.37840
127      zrgb(1, 4) =  0.014   ;   zrgb(2, 4) = 0.01736   ;   zrgb(3, 4) = 0.07518   ;   zrgb(4, 4) = 0.37859
128      zrgb(1, 5) =  0.016   ;   zrgb(2, 5) = 0.01782   ;   zrgb(3, 5) = 0.07539   ;   zrgb(4, 5) = 0.37879
129      zrgb(1, 6) =  0.018   ;   zrgb(2, 6) = 0.01831   ;   zrgb(3, 6) = 0.07562   ;   zrgb(4, 6) = 0.37900
130      zrgb(1, 7) =  0.020   ;   zrgb(2, 7) = 0.01885   ;   zrgb(3, 7) = 0.07586   ;   zrgb(4, 7) = 0.37923
131      zrgb(1, 8) =  0.022   ;   zrgb(2, 8) = 0.01943   ;   zrgb(3, 8) = 0.07613   ;   zrgb(4, 8) = 0.37948
132      zrgb(1, 9) =  0.025   ;   zrgb(2, 9) = 0.02005   ;   zrgb(3, 9) = 0.07641   ;   zrgb(4, 9) = 0.37976
133      zrgb(1,10) =  0.028   ;   zrgb(2,10) = 0.02073   ;   zrgb(3,10) = 0.07672   ;   zrgb(4,10) = 0.38005
134      zrgb(1,11) =  0.032   ;   zrgb(2,11) = 0.02146   ;   zrgb(3,11) = 0.07705   ;   zrgb(4,11) = 0.38036
135      zrgb(1,12) =  0.035   ;   zrgb(2,12) = 0.02224   ;   zrgb(3,12) = 0.07741   ;   zrgb(4,12) = 0.38070
136      zrgb(1,13) =  0.040   ;   zrgb(2,13) = 0.02310   ;   zrgb(3,13) = 0.07780   ;   zrgb(4,13) = 0.38107
137      zrgb(1,14) =  0.045   ;   zrgb(2,14) = 0.02402   ;   zrgb(3,14) = 0.07821   ;   zrgb(4,14) = 0.38146
138      zrgb(1,15) =  0.050   ;   zrgb(2,15) = 0.02501   ;   zrgb(3,15) = 0.07866   ;   zrgb(4,15) = 0.38189
139      zrgb(1,16) =  0.056   ;   zrgb(2,16) = 0.02608   ;   zrgb(3,16) = 0.07914   ;   zrgb(4,16) = 0.38235
140      zrgb(1,17) =  0.063   ;   zrgb(2,17) = 0.02724   ;   zrgb(3,17) = 0.07967   ;   zrgb(4,17) = 0.38285
141      zrgb(1,18) =  0.071   ;   zrgb(2,18) = 0.02849   ;   zrgb(3,18) = 0.08023   ;   zrgb(4,18) = 0.38338
142      zrgb(1,19) =  0.079   ;   zrgb(2,19) = 0.02984   ;   zrgb(3,19) = 0.08083   ;   zrgb(4,19) = 0.38396
143      zrgb(1,20) =  0.089   ;   zrgb(2,20) = 0.03131   ;   zrgb(3,20) = 0.08149   ;   zrgb(4,20) = 0.38458
144      zrgb(1,21) =  0.100   ;   zrgb(2,21) = 0.03288   ;   zrgb(3,21) = 0.08219   ;   zrgb(4,21) = 0.38526
145      zrgb(1,22) =  0.112   ;   zrgb(2,22) = 0.03459   ;   zrgb(3,22) = 0.08295   ;   zrgb(4,22) = 0.38598
146      zrgb(1,23) =  0.126   ;   zrgb(2,23) = 0.03643   ;   zrgb(3,23) = 0.08377   ;   zrgb(4,23) = 0.38676
147      zrgb(1,24) =  0.141   ;   zrgb(2,24) = 0.03842   ;   zrgb(3,24) = 0.08466   ;   zrgb(4,24) = 0.38761
148      zrgb(1,25) =  0.158   ;   zrgb(2,25) = 0.04057   ;   zrgb(3,25) = 0.08561   ;   zrgb(4,25) = 0.38852
149      zrgb(1,26) =  0.178   ;   zrgb(2,26) = 0.04289   ;   zrgb(3,26) = 0.08664   ;   zrgb(4,26) = 0.38950
150      zrgb(1,27) =  0.200   ;   zrgb(2,27) = 0.04540   ;   zrgb(3,27) = 0.08775   ;   zrgb(4,27) = 0.39056
151      zrgb(1,28) =  0.224   ;   zrgb(2,28) = 0.04811   ;   zrgb(3,28) = 0.08894   ;   zrgb(4,28) = 0.39171
152      zrgb(1,29) =  0.251   ;   zrgb(2,29) = 0.05103   ;   zrgb(3,29) = 0.09023   ;   zrgb(4,29) = 0.39294
153      zrgb(1,30) =  0.282   ;   zrgb(2,30) = 0.05420   ;   zrgb(3,30) = 0.09162   ;   zrgb(4,30) = 0.39428
154      zrgb(1,31) =  0.316   ;   zrgb(2,31) = 0.05761   ;   zrgb(3,31) = 0.09312   ;   zrgb(4,31) = 0.39572
155      zrgb(1,32) =  0.355   ;   zrgb(2,32) = 0.06130   ;   zrgb(3,32) = 0.09474   ;   zrgb(4,32) = 0.39727
156      zrgb(1,33) =  0.398   ;   zrgb(2,33) = 0.06529   ;   zrgb(3,33) = 0.09649   ;   zrgb(4,33) = 0.39894
157      zrgb(1,34) =  0.447   ;   zrgb(2,34) = 0.06959   ;   zrgb(3,34) = 0.09837   ;   zrgb(4,34) = 0.40075
158      zrgb(1,35) =  0.501   ;   zrgb(2,35) = 0.07424   ;   zrgb(3,35) = 0.10040   ;   zrgb(4,35) = 0.40270
159      zrgb(1,36) =  0.562   ;   zrgb(2,36) = 0.07927   ;   zrgb(3,36) = 0.10259   ;   zrgb(4,36) = 0.40480
160      zrgb(1,37) =  0.631   ;   zrgb(2,37) = 0.08470   ;   zrgb(3,37) = 0.10495   ;   zrgb(4,37) = 0.40707
161      zrgb(1,38) =  0.708   ;   zrgb(2,38) = 0.09056   ;   zrgb(3,38) = 0.10749   ;   zrgb(4,38) = 0.40952
162      zrgb(1,39) =  0.794   ;   zrgb(2,39) = 0.09690   ;   zrgb(3,39) = 0.11024   ;   zrgb(4,39) = 0.41216
163      zrgb(1,40) =  0.891   ;   zrgb(2,40) = 0.10374   ;   zrgb(3,40) = 0.11320   ;   zrgb(4,40) = 0.41502
164      zrgb(1,41) =  1.000   ;   zrgb(2,41) = 0.11114   ;   zrgb(3,41) = 0.11639   ;   zrgb(4,41) = 0.41809
165      zrgb(1,42) =  1.122   ;   zrgb(2,42) = 0.11912   ;   zrgb(3,42) = 0.11984   ;   zrgb(4,42) = 0.42142
166      zrgb(1,43) =  1.259   ;   zrgb(2,43) = 0.12775   ;   zrgb(3,43) = 0.12356   ;   zrgb(4,43) = 0.42500
167      zrgb(1,44) =  1.413   ;   zrgb(2,44) = 0.13707   ;   zrgb(3,44) = 0.12757   ;   zrgb(4,44) = 0.42887
168      zrgb(1,45) =  1.585   ;   zrgb(2,45) = 0.14715   ;   zrgb(3,45) = 0.13189   ;   zrgb(4,45) = 0.43304
169      zrgb(1,46) =  1.778   ;   zrgb(2,46) = 0.15803   ;   zrgb(3,46) = 0.13655   ;   zrgb(4,46) = 0.43754
170      zrgb(1,47) =  1.995   ;   zrgb(2,47) = 0.16978   ;   zrgb(3,47) = 0.14158   ;   zrgb(4,47) = 0.44240
171      zrgb(1,48) =  2.239   ;   zrgb(2,48) = 0.18248   ;   zrgb(3,48) = 0.14701   ;   zrgb(4,48) = 0.44765
172      zrgb(1,49) =  2.512   ;   zrgb(2,49) = 0.19620   ;   zrgb(3,49) = 0.15286   ;   zrgb(4,49) = 0.45331
173      zrgb(1,50) =  2.818   ;   zrgb(2,50) = 0.21102   ;   zrgb(3,50) = 0.15918   ;   zrgb(4,50) = 0.45942
174      zrgb(1,51) =  3.162   ;   zrgb(2,51) = 0.22703   ;   zrgb(3,51) = 0.16599   ;   zrgb(4,51) = 0.46601
175      zrgb(1,52) =  3.548   ;   zrgb(2,52) = 0.24433   ;   zrgb(3,52) = 0.17334   ;   zrgb(4,52) = 0.47313
176      zrgb(1,53) =  3.981   ;   zrgb(2,53) = 0.26301   ;   zrgb(3,53) = 0.18126   ;   zrgb(4,53) = 0.48080
177      zrgb(1,54) =  4.467   ;   zrgb(2,54) = 0.28320   ;   zrgb(3,54) = 0.18981   ;   zrgb(4,54) = 0.48909
178      zrgb(1,55) =  5.012   ;   zrgb(2,55) = 0.30502   ;   zrgb(3,55) = 0.19903   ;   zrgb(4,55) = 0.49803
179      zrgb(1,56) =  5.623   ;   zrgb(2,56) = 0.32858   ;   zrgb(3,56) = 0.20898   ;   zrgb(4,56) = 0.50768
180      zrgb(1,57) =  6.310   ;   zrgb(2,57) = 0.35404   ;   zrgb(3,57) = 0.21971   ;   zrgb(4,57) = 0.51810
181      zrgb(1,58) =  7.079   ;   zrgb(2,58) = 0.38154   ;   zrgb(3,58) = 0.23129   ;   zrgb(4,58) = 0.52934
182      zrgb(1,59) =  7.943   ;   zrgb(2,59) = 0.41125   ;   zrgb(3,59) = 0.24378   ;   zrgb(4,59) = 0.54147
183      zrgb(1,60) =  8.912   ;   zrgb(2,60) = 0.44336   ;   zrgb(3,60) = 0.25725   ;   zrgb(4,60) = 0.55457
184      zrgb(1,61) = 10.000   ;   zrgb(2,61) = 0.47804   ;   zrgb(3,61) = 0.27178   ;   zrgb(4,61) = 0.56870
185      !
186      prgb(:,:) = zrgb(2:4,:)
187      !
188      r_si2 = 1.e0 / zrgb(2, 1)        ! blue with the smallest chlorophyll concentration)
189      IF(lwp) WRITE(numout,*) '      RGB longest depth of extinction    r_si2 = ', r_si2
190      !
191      DO jc = 1, 61                         ! check
192         zchl = zrgb(1,jc)
193         irgb = NINT( 41 + 20.* LOG10( zchl ) + 1.e-15 )
194         IF(lwp) WRITE(numout,*) '    jc =', jc, '  Chl = ', zchl, '  irgb = ', irgb
195         IF( irgb /= jc ) THEN
196            IF(lwp) WRITE(numout,*) '    jc =', jc, '  Chl = ', zchl, '  Chl class = ', irgb
197            CALL ctl_stop( 'trc_oce_rgb : inconsistency in Chl tabulated attenuation coeff.' )
198         ENDIF
199      END DO
200      !
201   END SUBROUTINE trc_oce_rgb
202
203
204   SUBROUTINE trc_oce_rgb_read( prgb )
205      !!----------------------------------------------------------------------
206      !!                  ***  ROUTINE p4z_opt_init  ***
207      !!
208      !! ** Purpose :   Initialization of of the optical scheme
209      !!
210      !! ** Method  :   read the look up table for the optical coefficients
211      !!
212      !! ** input   :   xkrgb(61) precomputed array corresponding to the 
213      !!                          attenuation coefficient (from JM Andre)
214      !!----------------------------------------------------------------------
215      REAL(wp), DIMENSION(3,61), INTENT(out) ::   prgb   ! tabulated attenuation coefficient
216      !!
217      INTEGER  ::   jc, jb ! dummy loop indice
218      INTEGER  ::   irgb   ! temporary integer
219      REAL(wp) ::   zchl   ! temporary scalar
220      INTEGER  ::   numlight
221      !!----------------------------------------------------------------------
222      !
223      IF(lwp) THEN                         ! control print
224         WRITE(numout,*)
225         WRITE(numout,*) ' trc_oce_rgb_read : optical look-up table read in kRGB61.txt file'
226         WRITE(numout,*) ' ~~~~~~~~~~~~~~~~'
227         WRITE(numout,*) 
228      ENDIF
229      !
230      CALL ctl_opn( numlight, 'kRGB61.txt', 'OLD', 'FORMATTED', 'SEQUENTIAL', -1, numout, lwp )
231      DO jc = 1, 61
232         READ(numlight,*) zchl, ( prgb(jb,jc), jb = 1, 3 )
233         irgb = NINT( 41 + 20.* LOG10( zchl ) + 1.e-15 )   
234         IF(lwp) WRITE(numout,*) '    jc =', jc, '  Chl = ', zchl, '  irgb = ', irgb 
235         IF( irgb /= jc ) THEN 
236            IF(lwp) WRITE(numout,*) '    jc =', jc, '  Chl = ', zchl, '  Chl class = ', irgb
237            CALL ctl_stop( 'trc_oce_rgb_read : inconsistency in Chl tabulated attenuation coeff.' )
238         ENDIF
239      END DO
240      CLOSE( numlight )
241      !
242      r_si2 = 1.e0 / prgb(1, 1)      ! blue with the smallest chlorophyll concentration)
243      IF(lwp) WRITE(numout,*) '      RGB longest depth of extinction    r_si2 = ', r_si2
244      !
245   END SUBROUTINE trc_oce_rgb_read
246
247
248   FUNCTION trc_oce_ext_lev( prldex, pqsr_frc ) RESULT( pjl )
249      !!----------------------------------------------------------------------
250      !!                 ***  ROUTINE trc_oce_ext_lev  ***
251      !!       
252      !! ** Purpose :   compute max. level for light penetration
253      !!         
254      !! ** Method  :   the function provides the level at which irradiance
255      !!                becomes negligible (i.e. = 1.e-15 W/m2) for 3 or 2 bands light
256      !!                penetration: I(z) = pqsr_frc * EXP(hext/prldex) = 1.e-15 W/m2
257      !!                # prldex is the longest depth of extinction:
258      !!                   - prldex = 23 m (2 bands case)
259      !!                   - prldex = 62 m (3 bands case: blue waveband & 0.01 mg/m2 for the chlorophyll)
260      !!                # pqsr_frc is the fraction of solar radiation which penetrates,
261      !!                considering Qsr=240 W/m2 and rn_abs = 0.58:
262      !!                   - pqsr_frc = Qsr * (1-rn_abs)   = 1.00e2 W/m2 (2 bands case)
263      !!                   - pqsr_frc = Qsr * (1-rn_abs)/3 = 0.33e2 W/m2 (3 bands case & equi-partition)
264      !!
265      !!----------------------------------------------------------------------
266      REAL(wp), INTENT(in) ::   prldex    ! longest depth of extinction
267      REAL(wp), INTENT(in) ::   pqsr_frc  ! frac. solar radiation which penetrates
268      !!
269      INTEGER  ::   jk, pjl            ! levels
270      REAL(wp) ::   zhext              ! deepest level till which light penetrates
271      REAL(wp) ::   zprec = 15._wp     ! precision to reach -LOG10(1.e-15)
272      REAL(wp) ::   zem                ! temporary scalar
273      !!----------------------------------------------------------------------
274      !
275      ! It is not necessary to compute anything below the following depth
276      zhext = prldex * ( LOG(10._wp) * zprec + LOG(pqsr_frc) )
277      !
278      ! Level of light extinction
279      pjl = jpkm1
280      DO jk = jpkm1, 1, -1
281         IF(SUM(tmask(:,:,jk)) > 0 ) THEN
282            zem = MAXVAL( fsdepw(:,:,jk+1) * tmask(:,:,jk) )
283            IF( zem >= zhext )   pjl = jk                       ! last T-level reached by Qsr
284         ELSE
285            pjl = jk                                            ! or regional sea-bed depth
286         ENDIF
287      END DO
288      !
289   END FUNCTION trc_oce_ext_lev
290
291   !!======================================================================
292END MODULE trc_oce
Note: See TracBrowser for help on using the repository browser.