My Project
vdif_ts_gom.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 ! this subroutine is used to calculate the true temperature !
42 ! and salinity by including vertical diffusion implicitly. !
43 !==============================================================================|
44 ! See NOTES in VDIF_TS.F about possible optimization!
45 
46 ! REMOVED DEPTH CHECK FOR NONE WET DRY CASE. THIS IS A LEGACY FROM
47 ! ECOM-SI WHICH HAS LAND IN THE DOMAIN. IT IS NOT NEEDED IN FVCOM
48 
49 SUBROUTINE vdif_ts_gom(NCON1,F)
50 
51  !------------------------------------------------------------------------------|
52 
53  USE all_vars
54  USE mod_utils
55  USE bcs
56  USE mod_wd
57  IMPLICIT NONE
58  INTEGER :: I,K,NCON1,J,KI,hutemp
59  ! REAL(SP) :: TMP,TMP1,TMP2,TMP3,QTMP,GW,ZDEP,FKH,UMOLPR,WETFAC
60  ! REAL(SP), DIMENSION(0:MT,KB) :: F
61  ! REAL(SP), DIMENSION(M,KB) :: FF,AF,CF,VHF,VHPF,RAD
62  ! REAL(SP), DIMENSION(M) :: KHBOTTOM,WFSURF,SWRADF
63  REAL(DP) :: TMP,TMP1,TMP2,TMP3,QTMP,GW,ZDEP,FKH,UMOLPR,WETFAC
64  REAL(SP), DIMENSION(0:MT,KB) :: F
65  REAL(DP), DIMENSION(M,KB) :: FF,AF,CF,VHF,VHPF,RAD
66  REAL(DP), DIMENSION(M) :: KHBOTTOM,WFSURF,SWRADF,SASURF
67  REAL(DP), DIMENSION(M) :: COSGAMA1,COSGAMA2
68 
69 
70  IF(dbg_set(dbg_sbr)) WRITE(ipt,*)"Start: vdif_ts_gom :", ncon1
71 
72  umolpr = umol*1.e0_sp
73  sasurf = 0.0_sp
74  !
75  !------------------------------------------------------------------------------!
76  ! !
77  ! the following section solves the equation !
78  ! dti*(kh*f')'-f=-fb !
79  ! !
80  !------------------------------------------------------------------------------!
81 
82 
83  DO k = 2, kbm1
84  DO i = 1, m
85  IF(iswetn(i) == 1)THEN
86  fkh = kh(i,k)
87 
88  IF(k == kbm1) THEN
89  khbottom(i)=fkh
90  END IF
91 
92  af(i,k-1)=-dti*(fkh+umolpr)/(dz(i,k-1)*dzz(i,k-1)*d(i)*d(i))
93  cf(i,k)=-dti*(fkh+umolpr)/(dz(i,k)*dzz(i,k-1)*d(i)*d(i))
94  END IF
95  END DO
96  END DO
97 
98 
99  !------------------------------------------------------------------------------!
100  ! the net heat flux input. !
101  ! the method shown below can be used when we turn off the !
102  ! body force in subroutine advt. be sure this method could !
103  ! cause the surface overheated if the vertical resolution !
104  ! is not high enough. !
105  !------------------------------------------------------------------------------!
106 
107  SELECT CASE(ncon1)
108  CASE(1)
109 
110  rad = 0.0_sp
111  wfsurf = 0.0_sp
112  swradf = 0.0_sp
113 
114  IF(heating_type == 'flux')THEN
115  ! DO I=1,M
116  ! WFSURF(I)=WTSURF(I)
117  ! SWRADF(I)=SWRAD(I)
118  ! END DO
119  wfsurf(1:m)=wtsurf(1:m)
120  swradf(1:m)=swrad(1:m)
121 
122 
123  DO k = 1, kb
124  DO i = 1, m
125  IF(iswetn(i) == 1)THEN
126  zdep = z(i,k)*d(i)
127 
128  ! SPECIFIED PARAMETER FOR GOM CASE (JUNE 18, 2003)
129  IF(d(i) < 100.0_sp) THEN
130  rheat=0.78_sp
131  zeta1=1.4_sp
132  zeta2=6.3_sp
133  ELSE IF(d(i) > 150.0_sp) THEN
134  rheat=0.58_sp
135  zeta1=0.35_sp
136  zeta2=23.0_sp
137  ELSE
138  tmp1=(d(i)-100.0_sp)/(150.0_sp-100.0_sp)
139  rheat=0.78_sp+(0.58_sp-0.78_sp)*tmp1
140  zeta1=1.4_sp+ (0.35_sp-1.4_sp )*tmp1
141  zeta2=6.3_sp+ (23.0_sp-6.3_sp )*tmp1
142  END IF
143 
144  rad(i,k)=swradf(i)*(rheat*exp(zdep/zeta1)+(1-rheat)*exp(zdep/zeta2))
145  END IF
146 
147  END DO
148  END DO
149 
150  ELSE IF(heating_type == 'body') THEN !! H_TYPE = 'body_h'
151  rad = 0.0_sp
152  wfsurf = 0.0_sp
153  swradf = 0.0_sp
154  ELSE IF(heating_on) THEN
155  CALL fatal_error("HEATING TYPE IS SET INCORRECTLY:",&
156  & trim(heating_type) )
157  END IF
158 
159  CASE(2)
160 
161  swradf= 0.0_sp
162  wfsurf=0.0_sp
163  cosgama1=1.0_sp
164  ! SASURF(I)=-(QEVAP3(I)-QPREC3(I))*F(I,1)*ROFVROS*COSGAMA1(I)
165  !---Considering the salinity conservation, the sea surface salinity flux-----!
166  !---can be set as zero, that is----------------------------------------------!
167  sasurf = 0.0_sp
168  !----------------------------------------------------------------------------!
169  rad=0.0_sp
170 
171  CASE DEFAULT
172  CALL fatal_error('NCON NOT CORRECT IN VDIF_TS_GOM')
173  END SELECT
174 
175  !------------------------------------------------------------------------------!
176  ! surface bcs; wfsurf !
177  !------------------------------------------------------------------------------!
178 
179  DO i = 1, m
180  IF(iswetn(i) == 1)THEN
181  vhf(i,1) = af(i,1) / (af(i,1)-1.)
182  vhpf(i,1) = -dti *(sasurf(i)+wfsurf(i)-swradf(i) &
183  +rad(i,1)-rad(i,2)) / (-dz(i,1)*d(i)) - f(i,1)
184  vhpf(i,1) = vhpf(i,1) / (af(i,1)-1.)
185  END IF
186 
187  END DO
188 
189  DO k = 2, kbm2
190  DO i = 1, m
191  IF(iswetn(i) == 1)THEN
192  vhpf(i,k)=1./ (af(i,k)+cf(i,k)*(1.-vhf(i,k-1))-1.)
193  vhf(i,k) = af(i,k) * vhpf(i,k)
194  vhpf(i,k) = (cf(i,k)*vhpf(i,k-1)-dble(f(i,k)) &
195  +dti*(rad(i,k)-rad(i,k+1))/(d(i)*dz(i,k)))*vhpf(i,k)
196  END IF
197  END DO
198  END DO
199 
200 !!$ DO K = 1, KBM1
201 !!$ DO I = 1, M
202 !!$# if !defined (1)
203 !!$! IF (D(I) > 0.0_SP) THEN
204 !!$# else
205 !!$ IF(ISWETN(I) == 1)THEN
206 !!$# endif
207 !!$ FF(I,K) = F(I,K)
208 !!$# if defined (1)
209 !!$ END IF
210 !!$# endif
211 !!$ END DO
212 !!$ END DO
213 
214  DO k = 1, kbm1
215  DO i = 1, m
216  IF(iswetn(i) == 1)THEN
217  ff(i,k) = f(i,k)
218  END IF
219  END DO
220  END DO
221 
222  ! THIS PIECE OF CODE DESPERATELY NEEDS TO BE CLARIFIED
223  ! AND STREAMLINED
224  DO i = 1, m
225  IF (isonb(i) /= 2) THEN
226  ! IF(ISWETN(I) == 1 .AND.ISONB(I) /= 2)THEN
227  IF(iswetn(i) == 1)THEN
228  tmp1=pfpxb(i)*cos(sita_gd(i))+pfpyb(i)*sin(sita_gd(i))
229  tmp2=ah_bottom(i)*phpn(i)
230  tmp3=khbottom(i)+umolpr+ah_bottom(i)*phpn(i)*phpn(i)
231  tmp=tmp1*tmp2/tmp3*(khbottom(i)+umolpr)
232 
233  !----------------------------------------------------------------------
234  IF(noflux_bot_condition)THEN
235  SELECT CASE(ncon1)
236  CASE(1)
237  IF (tmp1 > 0.0_sp) tmp=0.0_sp
238  CASE(2)
239  IF (tmp1 < 0.0_sp) tmp=0.0_sp
240  tmp = -tmp
241  CASE DEFAULT
242  CALL fatal_error('NCON NOT CORRECT IN VDIF_TS_GOM')
243  END SELECT
244  ELSE
245  tmp = 0.0_sp
246  END IF
247 !!$ IF (TMP1 > 0.0_SP) TMP=0.0_SP
248 !!$ ! !also try TMP = 0.0_SP
249  !----------------------------------------------------------------------
250 !!$ THIS IS FOR AN OLDER VERSION OF GROUNDWATER
251 !!$ GW=0.0_SP
252 !!$ IF(NCON1 == 2) THEN
253 !!$ QTMP=-(F(I,KBM1)*D(I)*DZ(I,KBM1)*BFWDIS(I))/ &
254 !!$ (D(I)*DZ(I,KBM1)*ART1(I)+BFWDIS(I))
255 !!$ GW=DTI/D(I)/DZ(I,KBM1)*QTMP
256 !!$ IF (BFWDIS(I) /= 0.0_SP) TMP=0.0_SP
257 !!$
258 !!$ END IF
259 
260 
261  ff(i,kbm1) = (cf(i,kbm1)*vhpf(i,kbm2)-ff(i,kbm1)-gw+dti*(rad(i,kbm1)-rad(i,kb)-tmp)/(d(i)*dz(i,kbm1))) &
262  & /(cf(i,kbm1)*(1._sp-vhf(i,kbm2))-1._sp)
263 
264  END IF
265  END IF
266  END DO
267 
268  DO k = 2, kbm1
269  ki = kb - k
270  DO i = 1, m
271  IF(isonb(i) /= 2) THEN
272  ! IF(ISWETN(I) == 1 .AND.ISONB(I) /= 2)THEN
273  IF(iswetn(i) == 1)THEN
274  ff(i,ki) = (vhf(i,ki)*ff(i,ki+1)+vhpf(i,ki))
275  END IF
276  END IF
277  END DO
278  END DO
279 
280  DO i = 1, m
281  IF(iswetn(i)*iswetnt(i) == 1 )then
282  DO k = 1, kbm1
283  f(i,k) = ff(i,k)
284  END DO
285  END IF
286  END DO
287 
288  IF(dbg_set(dbg_sbr)) WRITE(ipt,*)"End: vdif_ts_gom"
289 
290  END SUBROUTINE vdif_ts_gom
291 !==============================================================================|
real(sp), dimension(:), allocatable, target d
Definition: mod_main.f90:1132
logical function dbg_set(vrb)
Definition: mod_utils.f90:182
real(sp), dimension(:), allocatable, target pfpxb
Definition: mod_main.f90:1342
real(sp), dimension(:), allocatable, target pfpyb
Definition: mod_main.f90:1343
real(sp), dimension(:), allocatable, target phpn
Definition: mod_main.f90:1341
real(sp), dimension(:), allocatable, target swrad
Definition: mod_main.f90:1177
real(sp), dimension(:,:), allocatable, target dzz
Definition: mod_main.f90:1093
real(sp), dimension(:), allocatable, target sita_gd
Definition: mod_main.f90:1344
real(sp), dimension(:,:), allocatable, target dz
Definition: mod_main.f90:1092
integer, dimension(:), allocatable iswetnt
Definition: mod_wd.f90:53
real(sp), dimension(:,:), allocatable, target kh
Definition: mod_main.f90:1294
real(sp), dimension(:,:), allocatable, target z
Definition: mod_main.f90:1090
subroutine vdif_ts_gom(NCON1, F)
Definition: vdif_ts_gom.f90:50
subroutine fatal_error(ER1, ER2, ER3, ER4)
Definition: mod_utils.f90:230
real(sp), dimension(:), allocatable, target ah_bottom
Definition: mod_main.f90:1345
real(sp), dimension(:), allocatable, target wtsurf
Definition: mod_main.f90:1178
integer, parameter dbg_sbr
Definition: mod_utils.f90:69
integer, dimension(:), allocatable, target isonb
Definition: mod_main.f90:1024
integer, dimension(:), allocatable iswetn
Definition: mod_wd.f90:51