My Project
fct_t.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 ! FLUX CONTROL FOR TEMPERATURE |
42 !==============================================================================|
43 
44 SUBROUTINE fct_t
45  !# if defined (1)
46 
47  !==============================================================================|
48  USE all_vars
49  USE mod_utils
50  USE bcs
51  USE mod_obcs
52  IMPLICIT NONE
53  REAL(SP):: TMAX,TMIN
54  INTEGER :: I,J,K
55  !==============================================================================|
56 
57 
58  IF(heating_type == 'body') RETURN
59 
60  IF(dbg_set(dbg_sbr)) WRITE(ipt,*)"Start: fct_t"
61 
62  nodes: DO i=1,m
63  ! SKIP OPEN BOUNDARY NODES
64  IF(iobcn > 0)THEN
65  DO j=1,iobcn
66  IF(i == i_obc_n(j)) cycle nodes
67  END DO
68  END IF
69 
70  ! SKIP RIVER INFLOW POINTS
71  IF(numqbc > 0)THEN
72  DO j=1,numqbc
73  IF(river_inflow_location == 'node')THEN
74  IF(i == inodeq(j)) cycle nodes
75  END IF
76  IF(river_inflow_location == 'edge')THEN
77  IF(i == n_icellq(j,1) .OR. i == n_icellq(j,2)) cycle nodes
78  END IF
79  END DO
80  END IF
81 
82  ! SKIP GROUND WATER INFLOW POINTS
83  IF(bfwdis(i) .GT. 0.0_sp .and. groundwater_temp_on) cycle nodes
84 
85  DO k=1,kbm1
86  tmax = maxval(t1(nbsn(i,1:ntsn(i)),k))
87  tmin = minval(t1(nbsn(i,1:ntsn(i)),k))
88 
89  IF(k == 1)THEN
90  tmax = max(tmax,(t1(i,k)*dz(i,k+1)+t1(i,k+1)*dz(i,k))/ &
91  (dz(i,k)+dz(i,k+1)))
92  tmin = min(tmin,(t1(i,k)*dz(i,k+1)+t1(i,k+1)*dz(i,k))/ &
93  (dz(i,k)+dz(i,k+1)))
94  ELSE IF(k == kbm1)THEN
95  tmax = max(tmax,(t1(i,k)*dz(i,k-1)+t1(i,k-1)*dz(i,k))/ &
96  (dz(i,k)+dz(i,k-1)))
97  tmin = min(tmin,(t1(i,k)*dz(i,k-1)+t1(i,k-1)*dz(i,k))/ &
98  (dz(i,k)+dz(i,k-1)))
99  ELSE
100  tmax = max(tmax,(t1(i,k)*dz(i,k-1)+t1(i,k-1)*dz(i,k))/ &
101  (dz(i,k)+dz(i,k-1)), &
102  (t1(i,k)*dz(i,k+1)+t1(i,k+1)*dz(i,k))/ &
103  (dz(i,k)+dz(i,k+1)))
104  tmin = min(tmin,(t1(i,k)*dz(i,k-1)+t1(i,k-1)*dz(i,k))/ &
105  (dz(i,k)+dz(i,k-1)), &
106  (t1(i,k)*dz(i,k+1)+t1(i,k+1)*dz(i,k))/ &
107  (dz(i,k)+dz(i,k+1)))
108  END IF
109 
110  IF(tmin-tf1(i,k) > 0.0_sp)tf1(i,k) = tmin
111  IF(tf1(i,k)-tmax > 0.0_sp)tf1(i,k) = tmax
112 
113  END DO
114 
115  END DO nodes
116 
117  IF(dbg_set(dbg_sbr)) WRITE(ipt,*)"End: fct_t"
118  !# endif
119 END SUBROUTINE fct_t
120 !==============================================================================|
121 
122 
integer, dimension(:), allocatable, target ntsn
Definition: mod_main.f90:1023
subroutine fct_t
Definition: fct_t.f90:45
logical function dbg_set(vrb)
Definition: mod_utils.f90:182
real(sp), dimension(:,:), allocatable, target t1
Definition: mod_main.f90:1307
integer iobcn
Definition: mod_main.f90:1777
real(sp), dimension(:,:), allocatable, target tf1
Definition: mod_main.f90:1310
integer, dimension(:), allocatable i_obc_n
Definition: mod_main.f90:1779
real(sp), dimension(:), allocatable, target bfwdis
Definition: mod_main.f90:1196
integer, dimension(:,:), allocatable, target n_icellq
Definition: mod_main.f90:1216
real(sp), dimension(:,:), allocatable, target dz
Definition: mod_main.f90:1092
integer, dimension(:,:), allocatable, target nbsn
Definition: mod_main.f90:1030
integer, parameter dbg_sbr
Definition: mod_utils.f90:69
integer, dimension(:), allocatable, target inodeq
Definition: mod_main.f90:1214