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 tags/nemo_v1_13_dev2/NEMO/OFF_SRC/ZDF – NEMO

source: tags/nemo_v1_13_dev2/NEMO/OFF_SRC/ZDF/zdfmxl.F90 @ 8068

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

nemo_v1_update_O29:RB: add header for OFFLINE component

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