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

source: trunk/NEMO/OPA_SRC/ZDF/zdfmxl.F90 @ 247

Last change on this file since 247 was 247, checked in by opalod, 19 years ago

CL : Add CVS Header and CeCILL licence information

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 9.0 KB
Line 
1MODULE zdfmxl
2   !!======================================================================
3   !!                       ***  MODULE  zdfmxl  ***
4   !! Ocean physics: mixed layer depth
5   !!======================================================================
6
7   !!----------------------------------------------------------------------
8   !!   zdf_mxl      : Compute the turbocline and mixed layer depths.
9   !!----------------------------------------------------------------------
10   !! * Modules used
11   USE oce             ! ocean dynamics and tracers variables
12   USE dom_oce         ! ocean space and time domain variables
13   USE zdf_oce         ! ocean vertical physics
14   USE in_out_manager  ! I/O manager
15
16   IMPLICIT NONE
17   PRIVATE
18
19   !! * Routine accessibility
20   PUBLIC zdf_mxl           ! called by step.F90
21
22   !! * Shared module variables
23   INTEGER, PUBLIC, DIMENSION(jpi,jpj) ::   &   !:
24      nmln                  !: number of level in the mixed layer
25   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   &   !:
26      hmld ,             &  !: mixing layer depth (turbocline) (m)
27      hmlp ,             &  !: mixed layer depth  (rho=rho0+zdcrit) (m)
28      hmlpt                 !: mixed layer depth at t-points (m)
29
30   !! * module variables
31   REAL(wp) ::   &
32      avt_c = 5.e-4_wp,  &  ! Kz criterion for the turbocline depth
33      rho_c = 0.01_wp       ! density criterion for mixed layer depth
34
35   !! * Substitutions
36#  include "domzgr_substitute.h90"
37   !!----------------------------------------------------------------------
38   !!   OPA 9.0 , LOCEAN-IPSL (2005)
39   !! $Header$
40   !! This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt
41   !!----------------------------------------------------------------------
42
43CONTAINS
44
45# if defined key_autotasking
46   !!----------------------------------------------------------------------
47   !!   'key_autotasking'                               j-k-i loop (j-slab)
48   !!----------------------------------------------------------------------
49
50   SUBROUTINE zdf_mxl( kt )
51      !!----------------------------------------------------------------------
52      !!                    ***  ROUTINE zdfmxl  ***
53      !!                   
54      !! ** Purpose :   Compute the turbocline depth and the mixed layer depth
55      !!      with a density criteria.
56      !!
57      !! ** Method  :   The turbocline depth is the depth at which the vertical
58      !!      eddy diffusivity coefficient (resulting from the vertical physics
59      !!      alone, not the isopycnal part, see trazdf.F) fall below a given
60      !!      value defined locally (avt_c here taken equal to 5 cm/s2)
61      !!
62      !! ** Action  :
63      !!
64      !! History :
65      !!   9.0  !  03-08  (G. Madec)  autotasking optimization
66      !!----------------------------------------------------------------------
67      !! * Arguments
68      INTEGER, INTENT( in ) ::   kt         ! ocean time-step index
69
70      !! * Local declarations
71      INTEGER ::   ji, jj, jk     ! dummy loop indices
72      INTEGER ::   ik             ! temporary integer
73      INTEGER, DIMENSION(jpi,jpj) ::   &
74         imld                     ! temporary workspace
75      !!----------------------------------------------------------------------
76
77      IF( kt == nit000 ) THEN
78         IF(lwp) WRITE(numout,*)
79         IF(lwp) WRITE(numout,*) 'zdf_mxl : mixed layer depth'
80         IF(lwp) WRITE(numout,*) '~~~~~~~   auto-tasking case : j-k-i loop'
81         IF(lwp) WRITE(numout,*)
82      ENDIF
83
84      !                                                ! ===============
85      DO jj = 1, jpj                                   !  Vertical slab
86         !                                             ! ===============
87
88         ! 1. Turbocline depth
89         ! -------------------
90         ! last w-level at which avt<avt_c (starting from the bottom jk=jpk)
91         ! (since avt(.,.,jpk)=0, we have jpk=< imld =< 2 )
92         DO jk = jpk, 2, -1
93            DO ji = 1, jpi
94               IF( avt(ji,jj,jk) < avt_c ) imld(ji,jj) = jk 
95            END DO
96         END DO
97
98         ! Turbocline depth and sub-turbocline temperature
99         DO ji = 1, jpi
100            ik = imld(ji,jj)
101            hmld (ji,jj) = fsdepw(ji,jj,ik) * tmask(ji,jj,1)
102         END DO
103
104!!gm idea
105!!   
106!!gm     DO jk = jpk, 2, -1
107!!gm        DO ji = 1, jpi
108!!gm           IF( avt(ji,jj,jk) < avt_c ) hmld(ji,jj) = fsdepw(ji,jj,jk) * tmask(ji,jj,1)
109!!gm        END DO
110!!gm     END DO
111!!gm
112
113         ! 2. Mixed layer depth
114         ! --------------------
115         ! Initialization to the number of w ocean point mbathy
116         nmln(:,jj) = mbathy(:,jj)
117
118         ! Last w-level at which rhop>=rho surf+rho_c (starting from jpk-1)
119         ! (rhop defined at t-point, thus jk-1 for w-level just above)
120         DO jk = jpkm1, 2, -1
121            DO ji = 1, jpi
122               IF( rhop(ji,jj,jk) > rhop(ji,jj,1) + rho_c )   nmln(ji,jj) = jk
123            END DO
124         END DO
125
126         ! Mixed layer depth
127         DO ji = 1, jpi
128            ik = nmln(ji,jj)
129            hmlp (ji,jj) = fsdepw(ji,jj,ik) * tmask(ji,jj,1)
130            hmlpt(ji,jj) = fsdept(ji,jj,ik-1)
131         END DO
132         !                                             ! ===============
133      END DO                                           !   End of slab
134      !                                                ! ===============
135
136      IF(l_ctl)   WRITE(numout,*) ' nmln : ', SUM( nmln(1:nictl+1,1:njctl+1) ), ' hmld: ', SUM( hmld(1:nictl+1,1:njctl+1) )
137
138   END SUBROUTINE zdf_mxl
139
140# else
141   !!----------------------------------------------------------------------
142   !!   Default option :                                         k-j-i loop
143   !!----------------------------------------------------------------------
144
145   SUBROUTINE zdf_mxl( kt )
146      !!----------------------------------------------------------------------
147      !!                  ***  ROUTINE zdfmxl  ***
148      !!                   
149      !! ** Purpose :   Compute the turbocline depth and the mixed layer depth
150      !!      with density criteria.
151      !!
152      !! ** Method  :   The turbocline depth is the depth at which the vertical
153      !!      eddy diffusivity coefficient (resulting from the vertical physics
154      !!      alone, not the isopycnal part, see trazdf.F) fall below a given
155      !!      value defined locally (avt_c here taken equal to 5 cm/s2)
156      !!
157      !! ** Action  :
158      !!
159      !! History :
160      !!        !  94-11  (M. Imbard)  Original code
161      !!   8.0  !  96-01  (E. Guilyardi)  sub mixed layer temp.
162      !!   8.1  !  97-07  (G. Madec)  optimization
163      !!   8.5  !  02-06  (G. Madec)  F90: Free form and module
164      !!----------------------------------------------------------------------
165      !! * Arguments
166      INTEGER, INTENT( in ) ::   kt         ! ocean time-step index
167
168      !! * Local declarations
169      INTEGER ::   ji, jj, jk     ! dummy loop indices
170      INTEGER ::   ik             ! temporary integer
171      INTEGER, DIMENSION(jpi,jpj) ::   &
172         imld                     ! temporary workspace
173      !!----------------------------------------------------------------------
174
175      IF( kt == nit000 ) THEN
176         IF(lwp) WRITE(numout,*)
177         IF(lwp) WRITE(numout,*) 'zdf_mxl : mixed layer depth'
178         IF(lwp) WRITE(numout,*) '~~~~~~~ '
179      ENDIF
180
181
182      ! 1. Turbocline depth
183      ! -------------------
184      ! last w-level at which avt<avt_c (starting from the bottom jk=jpk)
185      ! (since avt(.,.,jpk)=0, we have jpk=< imld =< 2 )
186      DO jk = jpk, 2, -1
187         DO jj = 1, jpj
188            DO ji = 1, jpi
189               IF( avt(ji,jj,jk) < avt_c ) imld(ji,jj) = jk 
190            END DO
191         END DO
192      END DO
193
194      ! Turbocline depth and sub-turbocline temperature
195      DO jj = 1, jpj
196         DO ji = 1, jpi
197            ik = imld(ji,jj)
198            hmld (ji,jj) = fsdepw(ji,jj,ik) * tmask(ji,jj,1)
199         END DO
200      END DO
201
202!!gm idea
203!!   
204!!gm  DO jk = jpk, 2, -1
205!!gm     DO jj = 1, jpj
206!!gm        DO ji = 1, jpi
207!!gm           IF( avt(ji,jj,jk) < avt_c ) hmld(ji,jj) = fsdepw(ji,jj,jk) * tmask(ji,jj,1)
208!!gm        END DO
209!!gm     END DO
210!!gm  END DO
211!!gm
212
213      ! 2. Mixed layer depth
214      ! --------------------
215      ! Initialization to the number of w ocean point mbathy
216      nmln(:,:) = mbathy(:,:)
217
218      ! Last w-level at which rhop>=rho surf+rho_c (starting from jpk-1)
219      ! (rhop defined at t-point, thus jk-1 for w-level just above)
220      DO jk = jpkm1, 2, -1
221         DO jj = 1, jpj
222            DO ji = 1, jpi
223               IF( rhop(ji,jj,jk) > rhop(ji,jj,1) + rho_c )   nmln(ji,jj) = jk
224            END DO
225         END DO
226      END DO
227
228      ! Mixed layer depth
229      DO jj = 1, jpj
230         DO ji = 1, jpi
231            ik = nmln(ji,jj)
232            hmlp (ji,jj) = fsdepw(ji,jj,ik) * tmask(ji,jj,1)
233            hmlpt(ji,jj) = fsdept(ji,jj,ik-1)
234         END DO
235      END DO
236
237      IF(l_ctl)   WRITE(numout,*) ' nmln : ', SUM( nmln(1:nictl+1,1:njctl+1) ), ' hmld: ', SUM( hmld(1:nictl+1,1:njctl+1) )
238
239   END SUBROUTINE zdf_mxl
240#endif
241
242   !!======================================================================
243END MODULE zdfmxl
Note: See TracBrowser for help on using the repository browser.