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

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

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


Revision 1.5 - (hide annotations) (download)
Sun Jan 3 19:17:01 2010 UTC (14 years, 4 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint63l, checkpoint63m, checkpoint63n, checkpoint63h, checkpoint63i, checkpoint63j, checkpoint63k, checkpoint63d, checkpoint63e, checkpoint63f, checkpoint63g, checkpoint63a, checkpoint63b, checkpoint63c, checkpoint63, checkpoint62c, checkpoint62b, checkpoint62a, checkpoint62g, checkpoint62f, checkpoint62e, checkpoint62d, checkpoint62k, checkpoint62j, checkpoint62i, checkpoint62h, checkpoint62o, checkpoint62n, checkpoint62m, checkpoint62l, checkpoint62s, checkpoint62r, checkpoint62q, checkpoint62p, checkpoint62w, checkpoint62v, checkpoint62u, checkpoint62t, checkpoint62z, checkpoint62y, checkpoint62x
Changes since 1.4: +3 -5 lines
avoid unused variables

1 jmc 1.5 C $Header: /u/gcmpack/MITgcm/pkg/pp81/pp81_calc.F,v 1.4 2009/10/08 20:08:20 jmc Exp $
2 mlosch 1.1 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 jmc 1.4 C *==========================================================*
15 mlosch 1.1 C | SUBROUTINE PP81_CALC |
16     C | o Compute all PP81 fields defined in PP81.h |
17 jmc 1.4 C *==========================================================*
18 mlosch 1.1 C | This subroutine is based on SPEM code |
19 jmc 1.4 C *==========================================================*
20 mlosch 1.1
21     C global parameters updated by pp_calc
22 jmc 1.4 C PPviscAz :: PP eddy viscosity coefficient (m^2/s)
23     C PPdiffKzT :: PP diffusion coefficient for temperature (m^2/s)
24 mlosch 1.1 C
25     C \ev
26    
27     C !USES: ============================================================
28 jmc 1.4 IMPLICIT NONE
29 mlosch 1.1 #include "SIZE.h"
30     #include "EEPARAMS.h"
31     #include "PARAMS.h"
32     #include "DYNVARS.h"
33     #include "PP81.h"
34     #include "FFIELDS.h"
35     #include "GRID.h"
36     #ifdef ALLOW_AUTODIFF_TAMC
37     #include "tamc.h"
38     #include "tamc_keys.h"
39     #endif /* ALLOW_AUTODIFF_TAMC */
40    
41     C !INPUT PARAMETERS: ===================================================
42     c Routine arguments
43 jmc 1.4 c bi, bj :: array indices on which to apply calculations
44     c myTime :: Current time in simulation
45     c myThid :: My Tread Id number
46 mlosch 1.1
47     INTEGER bi, bj
48 jmc 1.4 _RL myTime
49 mlosch 1.1 INTEGER myThid
50    
51     #ifdef ALLOW_PP81
52    
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 jmc 1.4 I bi, bj, K, iMin, iMax, jMin, jMax,
70     O RiNumber,
71 mlosch 1.1 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 jmc 1.4 PPviscAr(I,J,K,bi,bj) = MAX(PPviscTmp,viscArNr(k))
83 mlosch 1.1 PPdiffKr(I,J,K,bi,bj) = MAX(PPviscAr(I,J,K,bi,bj)/denom,
84 jmc 1.2 & diffKrNrT(k))
85 mlosch 1.1 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 jmc 1.4 CRT This is where the lower limit for subsurface layers
93     CRT (BRIOS special) is set.
94 jmc 1.5 IF ( (usingZCoords .AND. K .EQ. 2) .OR.
95     & (usingPCoords .AND. K .EQ. Nr) ) THEN
96 mlosch 1.1 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 jmc 1.4 ENDDO
101 mlosch 1.1 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 jmc 1.4 ENDDO
112 mlosch 1.1 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