/[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.4 - (hide annotations) (download)
Thu Oct 8 20:08:20 2009 UTC (14 years, 7 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint62, checkpoint61w, checkpoint61z, checkpoint61x, checkpoint61y
Changes since 1.3: +18 -20 lines
modif for vertical profile of background viscosity

1 jmc 1.4 C $Header: /u/gcmpack/MITgcm/pkg/pp81/pp81_calc.F,v 1.3 2005/04/06 18:45: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     #else /* ALLOW_AUTODIFF_TAMC */
40     integer ikppkey
41     #endif /* ALLOW_AUTODIFF_TAMC */
42    
43     C !INPUT PARAMETERS: ===================================================
44     c Routine arguments
45 jmc 1.4 c bi, bj :: array indices on which to apply calculations
46     c myTime :: Current time in simulation
47     c myThid :: My Tread Id number
48 mlosch 1.1
49     INTEGER bi, bj
50 jmc 1.4 _RL myTime
51 mlosch 1.1 INTEGER myThid
52    
53     #ifdef ALLOW_PP81
54    
55     C !LOCAL VARIABLES: ====================================================
56     c Local constants
57     C imin, imax, jmin, jmax - array computation indices
58     C RiNumber - Richardson Number
59     INTEGER I, J, K
60     INTEGER iMin ,iMax ,jMin ,jMax
61     _RL denom, PPviscTmp
62     _RL RiNumber(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
63     CEOP
64     iMin = 2-OLx
65     iMax = sNx+OLx-1
66     jMin = 2-OLy
67     jMax = sNy+OLy-1
68    
69     DO K = 2, Nr
70     CALL PP81_RI_NUMBER(
71 jmc 1.4 I bi, bj, K, iMin, iMax, jMin, jMax,
72     O RiNumber,
73 mlosch 1.1 I myTime, myThid )
74     DO J=jMin,jMax
75     DO I=iMin,iMax
76     IF ( RiNumber(I,J) .LT. RiLimit ) THEN
77     denom = 1.0 + PPalpha*RiLimit
78     PPviscTmp = PPviscMax
79     ELSE
80     denom = 1.0 + PPalpha*RiNumber(I,J)
81     PPviscTmp = PPnu0/(denom**PPnRi)
82     ENDIF
83     C assign a minium ( = background ) value
84 jmc 1.4 PPviscAr(I,J,K,bi,bj) = MAX(PPviscTmp,viscArNr(k))
85 mlosch 1.1 PPdiffKr(I,J,K,bi,bj) = MAX(PPviscAr(I,J,K,bi,bj)/denom,
86 jmc 1.2 & diffKrNrT(k))
87 mlosch 1.1 CML if ( k.eq.2 .and. i.ge.1 .and. i.le.sNx .and. j.eq.1)
88     CML & print '(A,3I3,5E14.5)', 'ml-pp81', I,J,K, RiLimit,
89     CML & RiNumber(I,J),denom,
90     CML & PPviscAr(I,J,K,bi,bj), PPdiffKr(I,J,K,bi,bj)
91     ENDDO
92     ENDDO
93     #ifdef ALLOW_PP81_LOWERBOUND
94 jmc 1.4 CRT This is where the lower limit for subsurface layers
95     CRT (BRIOS special) is set.
96 mlosch 1.1 IF ( (buoyancyRelation .EQ. 'OCEANIC' .AND. K .EQ. 2) .OR.
97     & (buoyancyRelation .EQ. 'OCEANICP' .AND. K .EQ. Nr) ) THEN
98     DO J=jMin,jMax
99     DO I=iMin,iMax
100     PPviscAr(I,J,K,bi,bj) = MAX(PPviscMin,PPviscAr(I,J,K,bi,bj))
101     PPdiffKr(I,J,K,bi,bj) = MAX(PPdiffMin,PPdiffKr(I,J,K,bi,bj))
102 jmc 1.4 ENDDO
103 mlosch 1.1 ENDDO
104     ENDIF
105     #endif /* ALLOW_PP81_LOWERBOUND */
106     C Mask land points
107     DO J=jMin,jMax
108     DO I=iMin,iMax
109     PPviscAr(I,J,K,bi,bj) = PPviscAr(I,J,K,bi,bj)
110     & * maskC(I,J,K,bi,bj)
111     PPdiffKr(I,J,K,bi,bj) = PPdiffKr(I,J,K,bi,bj)
112     & * maskC(I,J,K,bi,bj)
113 jmc 1.4 ENDDO
114 mlosch 1.1 ENDDO
115     C end K-loop
116     ENDDO
117    
118     #endif /* ALLOW_PP81 */
119    
120     RETURN
121     END

  ViewVC Help
Powered by ViewVC 1.1.22