/[MITgcm]/MITgcm/model/src/find_rho.F
ViewVC logotype

Annotation of /MITgcm/model/src/find_rho.F

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


Revision 1.4 - (hide annotations) (download)
Wed Apr 29 21:30:18 1998 UTC (26 years, 1 month ago) by adcroft
Branch: MAIN
CVS Tags: redigm, checkpoint1, checkpoint3, checkpoint2, kloop1, kloop2
Changes since 1.3: +66 -12 lines
Moved the "K loop" up to the subroutine dynamics().
find_rho() now returns a rho(:,:) for a layer calculated
using 'LINEAR' and 'POLY3' eqns of state and pressure reference
level kRef.

1 adcroft 1.4 C $Header: /u/gcmpack/models/MITgcmUV/model/src/find_rho.F,v 1.3 1998/04/24 02:05:40 cnh Exp $
2 cnh 1.1
3     #include "CPP_EEOPTIONS.h"
4    
5     ! ==============================================================================
6 adcroft 1.4 subroutine FIND_RHO(
7     I bi, bj, iMin, iMax, jMin, jMax, k, kRef, eqn,
8     O rholoc,
9     I myThid )
10     C /==========================================================\
11     C | o SUBROUTINE FIND_RHO |
12     C | Calculates [rho(S,T,z)-Rhonil] of a slice |
13     C |==========================================================|
14     C | |
15     C | k - is the Theta/Salt level |
16     C | kRef - determines pressure reference level |
17     C | (not used in 'LINEAR' mode) |
18     C | eqn - determines the eqn. of state: 'LINEAR' or 'POLY3' |
19     C | |
20     C \==========================================================/
21 cnh 1.1 implicit none
22     ! Common
23     #include "SIZE.h"
24     #include "DYNVARS.h"
25     #include "PARAMS.h"
26 adcroft 1.4 ! Arguments
27     integer bi,bj,iMin,iMax,jMin,jMax
28     integer k ! Level of Theta/Salt slice
29     integer kRef ! Pressure reference level
30     character*(*) eqn
31     _RL rholoc(1-Olx:sNx+Olx,1-Oly:sNy+Oly)
32     integer myThid
33 cnh 1.1 ! Local
34 adcroft 1.4 integer i,j
35     _RL refTemp,refSalt,sigRef,tP,sP,deltaSig
36 cnh 1.1 ! ------------------------------------------------------------------------------
37    
38 adcroft 1.4 if (eqn.eq.'LINEAR') then
39    
40     C ***NOTE***
41     C In the linear EOS, to make the static stability calculation meaningful
42     C we alway calculate the perturbation with respect to the surface level.
43     C **********
44     refTemp=tRef(1)
45     refSalt=sRef(1)
46    
47 cnh 1.1 do j=jMin,jMax
48     do i=iMin,iMax
49 adcroft 1.4 rholoc(i,j)=rhonil*(
50     & sBeta*( salt(i,j,k,bi,bj)-refSalt)
51     & -tAlpha*(theta(i,j,k,bi,bj)-refTemp) )
52 cnh 1.1 enddo
53     enddo
54 adcroft 1.4
55     elseif (eqn.eq.'POLY3') then
56    
57     refTemp=eosRefT(kRef)
58     refSalt=eosRefS(kRef)
59     sigRef=eosSig0(kRef)
60    
61     do j=jMin,jMax
62     do i=iMin,iMax
63     tP=theta(i,j,k,bi,bj)-refTemp
64     sP=salt(i,j,k,bi,bj)-refSalt
65     deltaSig=
66     & eosC(kRef,1)*tP
67     & +eosC(kRef,2) *sP
68     & +eosC(kRef,3)*tP*tP
69     & +eosC(kRef,4)*tP *sP
70     & +eosC(kRef,5) *sP*sP
71     & +eosC(kRef,6)*tP*tP*tP
72     & +eosC(kRef,7)*tP*tP *sP
73     & +eosC(kRef,8)*tP *sP*sP
74     & +eosC(kRef,9) *sP*sP*sP
75     rholoc(i,j)=1000.*(1.+sigRef+deltaSig)-Rhonil
76     enddo
77     enddo
78    
79     else
80     write(0,*) 'FIND_RHO: eqn = ',eqn
81     stop 'FIND_RHO: argument "eqn" has illegal value'
82     endif
83 cnh 1.1
84     ! ------------------------------------------------------------------------------
85     return
86     end
87     ! ==============================================================================

  ViewVC Help
Powered by ViewVC 1.1.22