/[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.6 - (show annotations) (download)
Wed Jun 27 22:39:09 2012 UTC (12 years ago) by jmc
Branch: MAIN
CVS Tags: checkpoint64y, checkpoint64x, checkpoint64z, checkpoint64q, checkpoint64p, checkpoint64s, checkpoint64r, checkpoint64u, checkpoint64t, checkpoint64w, checkpoint64v, checkpoint64i, checkpoint64h, checkpoint64k, checkpoint64j, checkpoint64m, checkpoint64l, checkpoint64o, checkpoint64n, checkpoint64a, checkpoint64c, checkpoint64b, checkpoint64e, checkpoint64d, checkpoint64g, checkpoint64f, checkpoint63p, checkpoint63q, checkpoint63r, checkpoint63s, checkpoint63o, checkpoint64, checkpoint65, checkpoint65b, checkpoint65c, checkpoint65a, checkpoint65f, checkpoint65d, checkpoint65e
Changes since 1.5: +10 -10 lines
pass sigmaR as argument (but not yet used); will save several RHO computation

1 C $Header: /u/gcmpack/MITgcm/pkg/pp81/pp81_calc.F,v 1.5 2010/01/03 19:17:01 jmc 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, sigmaR, myTime, myIter, 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
21 C global parameters updated by pp_calc
22 C PPviscAz :: PP eddy viscosity coefficient (m^2/s)
23 C PPdiffKzT :: PP diffusion coefficient for temperature (m^2/s)
24 C
25 C \ev
26
27 C !USES: ============================================================
28 IMPLICIT NONE
29 #include "SIZE.h"
30 #include "EEPARAMS.h"
31 #include "PARAMS.h"
32 #include "PP81.h"
33 #include "GRID.h"
34 #ifdef ALLOW_AUTODIFF_TAMC
35 #include "tamc.h"
36 #include "tamc_keys.h"
37 #endif /* ALLOW_AUTODIFF_TAMC */
38
39 C !INPUT PARAMETERS: ===================================================
40 C Routine arguments
41 C bi, bj :: Current tile indices
42 C sigmaR :: Vertical gradient of iso-neutral density
43 C myTime :: Current time in simulation
44 C myIter :: Current time-step number
45 C myThid :: My Thread Id number
46 INTEGER bi, bj
47 _RL sigmaR(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
48 _RL myTime
49 INTEGER myIter
50 INTEGER myThid
51
52 #ifdef ALLOW_PP81
53 C !LOCAL VARIABLES: ====================================================
54 c Local constants
55 C imin, imax, jmin, jmax - array computation indices
56 C RiNumber - Richardson Number
57 INTEGER I, J, K
58 INTEGER iMin ,iMax ,jMin ,jMax
59 _RL denom, PPviscTmp
60 _RL RiNumber(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
61 CEOP
62 iMin = 2-OLx
63 iMax = sNx+OLx-1
64 jMin = 2-OLy
65 jMax = sNy+OLy-1
66
67 DO K = 2, Nr
68 CALL PP81_RI_NUMBER(
69 I bi, bj, K, iMin, iMax, jMin, jMax,
70 O RiNumber,
71 I myTime, myThid )
72 DO J=jMin,jMax
73 DO I=iMin,iMax
74 IF ( RiNumber(I,J) .LT. RiLimit ) THEN
75 denom = 1.0 + PPalpha*RiLimit
76 PPviscTmp = PPviscMax
77 ELSE
78 denom = 1.0 + PPalpha*RiNumber(I,J)
79 PPviscTmp = PPnu0/(denom**PPnRi)
80 ENDIF
81 C assign a minium ( = background ) value
82 PPviscAr(I,J,K,bi,bj) = MAX(PPviscTmp,viscArNr(k))
83 PPdiffKr(I,J,K,bi,bj) = MAX(PPviscAr(I,J,K,bi,bj)/denom,
84 & diffKrNrT(k))
85 CML if ( k.eq.2 .and. i.ge.1 .and. i.le.sNx .and. j.eq.1)
86 CML & print '(A,3I3,5E14.5)', 'ml-pp81', I,J,K, RiLimit,
87 CML & RiNumber(I,J),denom,
88 CML & PPviscAr(I,J,K,bi,bj), PPdiffKr(I,J,K,bi,bj)
89 ENDDO
90 ENDDO
91 #ifdef ALLOW_PP81_LOWERBOUND
92 CRT This is where the lower limit for subsurface layers
93 CRT (BRIOS special) is set.
94 IF ( (usingZCoords .AND. K .EQ. 2) .OR.
95 & (usingPCoords .AND. K .EQ. Nr) ) THEN
96 DO J=jMin,jMax
97 DO I=iMin,iMax
98 PPviscAr(I,J,K,bi,bj) = MAX(PPviscMin,PPviscAr(I,J,K,bi,bj))
99 PPdiffKr(I,J,K,bi,bj) = MAX(PPdiffMin,PPdiffKr(I,J,K,bi,bj))
100 ENDDO
101 ENDDO
102 ENDIF
103 #endif /* ALLOW_PP81_LOWERBOUND */
104 C Mask land points
105 DO J=jMin,jMax
106 DO I=iMin,iMax
107 PPviscAr(I,J,K,bi,bj) = PPviscAr(I,J,K,bi,bj)
108 & * maskC(I,J,K,bi,bj)
109 PPdiffKr(I,J,K,bi,bj) = PPdiffKr(I,J,K,bi,bj)
110 & * maskC(I,J,K,bi,bj)
111 ENDDO
112 ENDDO
113 C end K-loop
114 ENDDO
115
116 #endif /* ALLOW_PP81 */
117
118 RETURN
119 END

  ViewVC Help
Powered by ViewVC 1.1.22