/[MITgcm]/MITgcm/pkg/pp81/pp81_calc.F
ViewVC logotype

Contents of /MITgcm/pkg/pp81/pp81_calc.F

Parent Directory Parent Directory | Revision Log Revision Log | View Revision Graph Revision Graph


Revision 1.2 - (show annotations) (download)
Sun Oct 17 23:12:59 2004 UTC (19 years, 7 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint57d_post, checkpoint57b_post, checkpoint57c_pre, checkpoint55j_post, checkpoint56b_post, checkpoint57e_post, checkpoint55h_post, checkpoint56c_post, checkpoint57f_pre, checkpoint57a_post, checkpoint57a_pre, checkpoint55i_post, checkpoint57, checkpoint56, eckpoint57e_pre, checkpoint57c_post, checkpoint56a_post
Changes since 1.1: +2 -2 lines
allow to set a vertical profile of vertical diffusivity for T & S

1 C $Header: /u/gcmpack/MITgcm/pkg/pp81/pp81_calc.F,v 1.1 2004/09/02 09:11:54 mlosch Exp $
2 C $Name: $
3
4 #include "PP81_OPTIONS.h"
5
6 CBOP
7 C !ROUTINE: PP81_CALC
8
9 C !INTERFACE: =======================================================
10 subroutine PP81_CALC(
11 I bi, bj, myTime, myThid )
12
13 C !DESCRIPTION: \bv
14 C /==========================================================\
15 C | SUBROUTINE PP81_CALC |
16 C | o Compute all PP81 fields defined in PP81.h |
17 C |==========================================================|
18 C | This subroutine is based on SPEM code |
19 C \==========================================================/
20 IMPLICIT NONE
21 C
22 C--------------------------------------------------------------------
23
24 C global parameters updated by pp_calc
25 C PPviscAz - PP eddy viscosity coefficient (m^2/s)
26 C PPdiffKzT - PP diffusion coefficient for temperature (m^2/s)
27 C
28 C \ev
29
30 C !USES: ============================================================
31 #include "SIZE.h"
32 #include "EEPARAMS.h"
33 #include "PARAMS.h"
34 #include "DYNVARS.h"
35 #include "PP81.h"
36 #include "FFIELDS.h"
37 #include "GRID.h"
38 #ifdef ALLOW_AUTODIFF_TAMC
39 #include "tamc.h"
40 #include "tamc_keys.h"
41 #else /* ALLOW_AUTODIFF_TAMC */
42 integer ikppkey
43 #endif /* ALLOW_AUTODIFF_TAMC */
44
45 EXTERNAL DIFFERENT_MULTIPLE
46 LOGICAL DIFFERENT_MULTIPLE
47
48 C !INPUT PARAMETERS: ===================================================
49 c Routine arguments
50 c bi, bj - array indices on which to apply calculations
51 c myTime - Current time in simulation
52
53 INTEGER bi, bj
54 INTEGER myThid
55 _RL myTime
56
57 #ifdef ALLOW_PP81
58
59 C !LOCAL VARIABLES: ====================================================
60 c Local constants
61 C imin, imax, jmin, jmax - array computation indices
62 C RiNumber - Richardson Number
63 INTEGER I, J, K
64 INTEGER iMin ,iMax ,jMin ,jMax
65 _RL denom, PPviscTmp
66 _RL RiNumber(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
67 CEOP
68 iMin = 2-OLx
69 iMax = sNx+OLx-1
70 jMin = 2-OLy
71 jMax = sNy+OLy-1
72
73 DO K = 2, Nr
74 CALL PP81_RI_NUMBER(
75 I bi, bj, K, iMin, iMax, jMin, jMax,
76 O RiNumber,
77 I myTime, myThid )
78 DO J=jMin,jMax
79 DO I=iMin,iMax
80 IF ( RiNumber(I,J) .LT. RiLimit ) THEN
81 denom = 1.0 + PPalpha*RiLimit
82 PPviscTmp = PPviscMax
83 ELSE
84 denom = 1.0 + PPalpha*RiNumber(I,J)
85 PPviscTmp = PPnu0/(denom**PPnRi)
86 ENDIF
87 C assign a minium ( = background ) value
88 PPviscAr(I,J,K,bi,bj) = MAX(PPviscTmp,viscAr)
89 PPdiffKr(I,J,K,bi,bj) = MAX(PPviscAr(I,J,K,bi,bj)/denom,
90 & diffKrNrT(k))
91 CML if ( k.eq.2 .and. i.ge.1 .and. i.le.sNx .and. j.eq.1)
92 CML & print '(A,3I3,5E14.5)', 'ml-pp81', I,J,K, RiLimit,
93 CML & RiNumber(I,J),denom,
94 CML & PPviscAr(I,J,K,bi,bj), PPdiffKr(I,J,K,bi,bj)
95 ENDDO
96 ENDDO
97 #ifdef ALLOW_PP81_LOWERBOUND
98 CRT This is where the lower limit for subsurface layers
99 CRT (BRIOS special) is set.
100 IF ( (buoyancyRelation .EQ. 'OCEANIC' .AND. K .EQ. 2) .OR.
101 & (buoyancyRelation .EQ. 'OCEANICP' .AND. K .EQ. Nr) ) THEN
102 DO J=jMin,jMax
103 DO I=iMin,iMax
104 PPviscAr(I,J,K,bi,bj) = MAX(PPviscMin,PPviscAr(I,J,K,bi,bj))
105 PPdiffKr(I,J,K,bi,bj) = MAX(PPdiffMin,PPdiffKr(I,J,K,bi,bj))
106 ENDDO
107 ENDDO
108 ENDIF
109 #endif /* ALLOW_PP81_LOWERBOUND */
110 C Mask land points
111 DO J=jMin,jMax
112 DO I=iMin,iMax
113 PPviscAr(I,J,K,bi,bj) = PPviscAr(I,J,K,bi,bj)
114 & * maskC(I,J,K,bi,bj)
115 PPdiffKr(I,J,K,bi,bj) = PPdiffKr(I,J,K,bi,bj)
116 & * maskC(I,J,K,bi,bj)
117 ENDDO
118 ENDDO
119 C end K-loop
120 ENDDO
121
122 #endif /* ALLOW_PP81 */
123
124 RETURN
125 END
126

  ViewVC Help
Powered by ViewVC 1.1.22