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

Last change on this file since 106 was 106, checked in by opalod, 20 years ago

CT : UPDATE067 : Add control indices nictl, njctl used in SUM function output to compare mono versus multi procs runs

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