/[MITgcm]/MITgcm/pkg/down_slope/dwnslp_calc_rho.F
ViewVC logotype

Contents of /MITgcm/pkg/down_slope/dwnslp_calc_rho.F

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


Revision 1.3 - (show annotations) (download)
Fri Apr 23 13:19:26 2010 UTC (14 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, checkpoint63l, checkpoint63m, checkpoint63n, checkpoint63o, checkpoint63h, checkpoint63i, checkpoint63j, checkpoint63k, checkpoint63d, checkpoint63e, checkpoint63f, checkpoint63g, checkpoint63a, checkpoint63b, checkpoint63c, checkpoint64, checkpoint65, checkpoint63, checkpoint65r, checkpoint65s, checkpoint65p, checkpoint65q, checkpoint65t, checkpoint65j, checkpoint65k, checkpoint65h, checkpoint65i, checkpoint65n, checkpoint65o, checkpoint65l, checkpoint65m, checkpoint65b, checkpoint65c, checkpoint65a, checkpoint65f, checkpoint65g, checkpoint65d, checkpoint65e, checkpoint62g, checkpoint62f, checkpoint62k, checkpoint62j, checkpoint62i, checkpoint62h, checkpoint62o, checkpoint62n, checkpoint62m, checkpoint62l, checkpoint62s, checkpoint62r, checkpoint62q, checkpoint62p, checkpoint62w, checkpoint62v, checkpoint62u, checkpoint62t, checkpoint62z, checkpoint62y, checkpoint62x
Changes since 1.2: +2 -2 lines
fix propagating typo in variable description

1 C $Header: /u/gcmpack/MITgcm/pkg/down_slope/dwnslp_calc_rho.F,v 1.2 2008/09/22 17:57:05 jmc Exp $
2 C $Name: $
3
4 #include "DWNSLP_OPTIONS.h"
5
6 CBOP
7 C !ROUTINE: DWNSLP_CALC_RHO
8 C !INTERFACE:
9 SUBROUTINE DWNSLP_CALC_RHO(
10 I tFld, sFld,
11 O rhoLoc,
12 I k, bi, bj, myTime, myIter, myThid )
13
14 C !DESCRIPTION: \bv
15 C *==========================================================*
16 C | SUBROUTINE DWNSLP_CALC_RHO
17 C | o Calculates [rho(S,T,z)-rhoConst] of a 2-D slice
18 C | filling land-points with bottom density
19 C *==========================================================*
20 C | Note: could move this S/R to model/src (if needed) since
21 C | it does not contain anything specific to Down-Slope pkg
22 C *==========================================================*
23 C \ev
24
25 C !USES:
26 IMPLICIT NONE
27
28 C === Global variables ===
29 #include "SIZE.h"
30 #include "EEPARAMS.h"
31 #include "PARAMS.h"
32 #include "GRID.h"
33
34 C !INPUT/OUTPUT PARAMETERS:
35 C === Routine arguments ===
36 C tFld :: Pot.Temperature (3-D array)
37 C sFld :: Salinity (3-D array)
38 C rhoLoc :: In-situ density [kg/m3] (2-D array) computed at z=rC ;
39 C k :: current vertical index
40 C bi,bj :: Tile indices
41 C myTime :: Current time in simulation
42 C myIter :: Current time-step number
43 C myThid :: my Thread Id number
44 _RL tFld (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr,nSx,nSy)
45 _RL sFld (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr,nSx,nSy)
46 _RL rhoLoc (1-Olx:sNx+Olx,1-Oly:sNy+Oly)
47 INTEGER k, bi, bj
48 _RL myTime
49 INTEGER myIter, myThid
50 CEOP
51
52 C !LOCAL VARIABLES:
53 C === Local variables ===
54 C msgBuf :: Informational/error message buffer
55 c CHARACTER*(MAX_LEN_MBUF) msgBuf
56 _RL tLoc (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
57 _RL sLoc (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
58 INTEGER i,j,kl
59
60 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
61
62 C-- make a local copy of Temp & salt :
63 DO j=1-OLy,sNy+OLy
64 DO i=1-OLx,sNx+OLx
65 c kl = k
66 c IF ( kLowC(i,j,bi,bj).GE.1 ) THEN
67 c IF ( k.GT.kLowC (i,j,bi,bj) ) k = kLowC (i,j,bi,bj)
68 c IF ( k.LT.kSurfC(i,j,bi,bj) ) k = kSurfC(i,j,bi,bj)
69 c ENDIF
70 C- same as above, using min,max:
71 kl = MIN( MAX(k,kSurfC(i,j,bi,bj)), MAX(kLowC(i,j,bi,bj),1) )
72 tLoc(i,j) = tFld(i,j,kl,bi,bj)
73 sLoc(i,j) = sFld(i,j,kl,bi,bj)
74 C---- This is a hack to get the right full pressure (from calc_phi_hyd)
75 C in EOS when using useDynP_inEos_Zc ; the way to go arround would
76 C be to store rhoInSitu in a common block and use it in calc_phi_hyd
77 C (would also save one 3-D EOS computation + T & S storage for TAF).
78 c tFld(i,j,k,bi,bj) = tLoc(i,j)
79 c sFld(i,j,k,bi,bj) = sLoc(i,j)
80 C----
81 ENDDO
82 ENDDO
83
84 CALL FIND_RHO_2D(
85 I 1-OLx, sNx+OLx, 1-OLy, sNy+OLy, k,
86 I tLoc, sLoc,
87 O rhoLoc,
88 I k, bi, bj, myThid )
89
90 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
91
92 RETURN
93 END

  ViewVC Help
Powered by ViewVC 1.1.22