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.
p4zint.F90 in NEMO/trunk/src/TOP/PISCES/P4Z – NEMO

source: NEMO/trunk/src/TOP/PISCES/P4Z/p4zint.F90

Last change on this file was 15459, checked in by cetlod, 2 years ago

Various bug fixes and more comments in PISCES routines ; sette test OK in debug mode, nn_hls=1/2, with tiling ; run.stat unchanged ; of course tracer.stat different

  • Property svn:keywords set to Id
File size: 4.8 KB
Line 
1MODULE p4zint
2   !!=========================================================================
3   !!                         ***  MODULE p4zint  ***
4   !! TOP :   PISCES interpolation and computation of various accessory fields
5   !!=========================================================================
6   !! History :   1.0  !  2004-03 (O. Aumont) Original code
7   !!             2.0  !  2007-12  (C. Ethe, G. Madec)  F90
8   !!----------------------------------------------------------------------
9   !!   p4z_int        :  interpolation and computation of various accessory fields
10   !!----------------------------------------------------------------------
11   USE oce_trc         !  shared variables between ocean and passive tracers
12   USE trc             !  passive tracers common variables
13   USE sms_pisces      !  PISCES Source Minus Sink variables
14
15   IMPLICIT NONE
16   PRIVATE
17
18   PUBLIC   p4z_int 
19   REAL(wp) ::   xksilim = 16.5e-6_wp   ! Half-saturation constant for the Si half-saturation constant computation
20
21#  include "do_loop_substitute.h90"
22   !!----------------------------------------------------------------------
23   !! NEMO/TOP 4.0 , NEMO Consortium (2018)
24   !! $Id$
25   !! Software governed by the CeCILL license (see ./LICENSE)
26   !!----------------------------------------------------------------------
27CONTAINS
28
29   SUBROUTINE p4z_int( kt, Kbb, Kmm )
30      !!---------------------------------------------------------------------
31      !!                     ***  ROUTINE p4z_int  ***
32      !!
33      !! ** Purpose :   interpolation and computation of various accessory fields
34      !!
35      !!---------------------------------------------------------------------
36      INTEGER, INTENT( in ) ::   kt       ! ocean time-step index
37      INTEGER, INTENT( in ) ::   Kbb, Kmm ! time level indices
38      !
39      INTEGER  :: ji, jj, jk              ! dummy loop indices
40      REAL(wp) :: zrum, zcodel, zargu, zvar
41      !!---------------------------------------------------------------------
42      !
43      IF( ln_timing )   CALL timing_start('p4z_int')
44      !
45      ! Computation of phyto and zoo metabolic rate
46      ! -------------------------------------------
47      ! Generic temperature dependence (Eppley, 1972)
48      tgfunc (:,:,:) = EXP( 0.0631 * ts(:,:,:,jp_tem,Kmm) )
49      ! Temperature dependence of mesozooplankton (Buitenhuis et al. (2005))
50      tgfunc2(:,:,:) = EXP( 0.0761 * ts(:,:,:,jp_tem,Kmm) )
51
52
53      ! Computation of the silicon dependant half saturation  constant for silica uptake
54      ! This is based on an old study by Pondaven et al. (1998)
55      ! --------------------------------------------------------------------------------
56      DO_2D( nn_hls, nn_hls, nn_hls, nn_hls )
57         zvar = tr(ji,jj,1,jpsil,Kbb) * tr(ji,jj,1,jpsil,Kbb)
58         xksimax(ji,jj) = MAX( xksimax(ji,jj), ( 1.+ 7.* zvar / ( xksilim * xksilim + zvar ) ) * 1e-6 )
59      END_2D
60      !
61      ! At the end of each year, the half saturation constant for silica is
62      ! updated as this is based on the highest concentration reached over
63      ! the year
64      ! -------------------------------------------------------------------
65      IF( nday_year == nyear_len(1) ) THEN
66         xksi   (:,:) = xksimax(:,:)
67         xksimax(:,:) = 0._wp
68      ENDIF
69      !
70      ! compute the day length depending on latitude and the day
71      ! Astronomical parameterization taken from HAMOCC3
72      zrum = REAL( nday_year - 80, wp ) / REAL( nyear_len(1), wp )
73      zcodel = ASIN(  SIN( zrum * rpi * 2._wp ) * SIN( rad * 23.5_wp )  )
74
75      ! day length in hours
76      strn(:,:) = 0.
77      DO_2D( nn_hls, nn_hls, nn_hls, nn_hls )
78         zargu = TAN( zcodel ) * TAN( gphit(ji,jj) * rad )
79         zargu = MAX( -1., MIN(  1., zargu ) )
80         strn(ji,jj) = MAX( 0.0, 24. - 2. * ACOS( zargu ) / rad / 15. )
81      END_2D
82      !
83      DO_3D( nn_hls, nn_hls, nn_hls, nn_hls, 1, jpkm1 )
84        ! denitrification factor computed from O2 levels
85         ! This factor diagnoses below which level of O2 denitrification
86         ! is active
87         nitrfac(ji,jj,jk) = MAX(  0.e0, 0.4 * ( 6.e-6  - tr(ji,jj,jk,jpoxy,Kbb) )    &
88            &                                / ( oxymin + tr(ji,jj,jk,jpoxy,Kbb) )  )
89         nitrfac(ji,jj,jk) = MIN( 1., nitrfac(ji,jj,jk) )
90         !
91         ! redox factor computed from NO3 levels
92         ! This factor diagnoses below which level of NO3 additional redox
93         ! reactions are taking place.
94         nitrfac2(ji,jj,jk) = MAX( 0.e0,       ( 1.E-6 - tr(ji,jj,jk,jpno3,Kbb) )  &
95            &                                / ( 1.E-6 + tr(ji,jj,jk,jpno3,Kbb) ) )
96         nitrfac2(ji,jj,jk) = MIN( 1., nitrfac2(ji,jj,jk) )
97      END_3D
98      !
99      IF( ln_timing )   CALL timing_stop('p4z_int')
100      !
101   END SUBROUTINE p4z_int
102
103   !!======================================================================
104END MODULE p4zint
Note: See TracBrowser for help on using the repository browser.