My Project
conv_over.f90
Go to the documentation of this file.
1 
2 
3 
4 
5 
6 
7 
8 
9 
10 
11 
12 !/===========================================================================/
13 ! Copyright (c) 2007, The University of Massachusetts Dartmouth
14 ! Produced at the School of Marine Science & Technology
15 ! Marine Ecosystem Dynamics Modeling group
16 ! All rights reserved.
17 !
18 ! FVCOM has been developed by the joint UMASSD-WHOI research team. For
19 ! details of authorship and attribution of credit please see the FVCOM
20 ! technical manual or contact the MEDM group.
21 !
22 !
23 ! This file is part of FVCOM. For details, see http://fvcom.smast.umassd.edu
24 ! The full copyright notice is contained in the file COPYRIGHT located in the
25 ! root directory of the FVCOM code. This original header must be maintained
26 ! in all distributed versions.
27 !
28 ! THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS "AS IS"
29 ! AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO,
30 ! THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR
31 ! PURPOSE ARE DISCLAIMED.
32 !
33 !/---------------------------------------------------------------------------/
34 ! CVS VERSION INFORMATION
35 ! $Id$
36 ! $Name$
37 ! $Revision$
38 !/===========================================================================/
39 
40 !==============================================================================|
41 ! ADJUST THE VERTICAL WATER COLUMN WHEN UNSTABLE |
42 !==============================================================================|
43 
44  SUBROUTINE conv_over
45 
46 !==============================================================================|
47  USE all_vars
48  USE mod_utils
49  IMPLICIT NONE
50  REAL(SP):: AVE_T,AVE_S,AVE_R
51  INTEGER :: I,K,KK,J1,J2,J3
52 !==============================================================================|
53 
54  IF (dbg_set(dbg_sbr)) WRITE(ipt,*) "Start: conv_over"
55 
56 
57 !--APPROXIMATE CONVECTIVE OVERTURNING------------------------------------------!
58 
59  DO i=1,m
60  DO k=kbm1,2,-1
61  DO kk=k-1,1,-1
62  IF(rho1(i,k) < rho1(i,kk)) THEN
63  ave_t = sum( t1(i,kk:k))/float(k-kk+1)
64  ave_s = sum( s1(i,kk:k))/float(k-kk+1)
65  ave_r = sum(rho1(i,kk:k))/float(k-kk+1)
66  t1(i,kk:k) = ave_t
67  s1(i,kk:k) = ave_s
68  rho1(i,kk:k) = ave_r
69  END IF
70  END DO
71  END DO
72  END DO
73 
74 !-----RECALCULATE ELEMENT-BASED VALUES OF SALINITY/TEMP/DENSITY----------------!
75 
76  DO i=1,n
77  j1=nv(i,1) ; j2 = nv(i,2) ; j3 = nv(i,3)
78  DO k=1,kbm1
79  t(i,k) = one_third*( t1(j1,k)+ t1(j2,k)+ t1(j3,k))
80  s(i,k) = one_third*( s1(j1,k)+ s1(j2,k)+ s1(j3,k))
81  END DO
82  END DO
83 
84  IF (dbg_set(dbg_sbr)) WRITE(ipt,*) "End: conv_over"
85 
86  RETURN
87  END SUBROUTINE conv_over
88 !==============================================================================|
89 
subroutine conv_over
Definition: conv_over.f90:45
real(sp), dimension(:,:), allocatable, target s
Definition: mod_main.f90:1288
logical function dbg_set(vrb)
Definition: mod_utils.f90:182
real(sp), dimension(:,:), allocatable, target rho1
Definition: mod_main.f90:1309
real(sp), dimension(:,:), allocatable, target t1
Definition: mod_main.f90:1307
real(sp), dimension(:,:), allocatable, target s1
Definition: mod_main.f90:1308
integer, dimension(:,:), allocatable, target nv
Definition: mod_main.f90:1018
real(sp), dimension(:,:), allocatable, target t
Definition: mod_main.f90:1286
integer, parameter dbg_sbr
Definition: mod_utils.f90:69