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

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

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


Revision 1.4 - (hide annotations) (download)
Wed Sep 18 16:38:02 2002 UTC (21 years, 8 months ago) by mlosch
Branch: MAIN
CVS Tags: checkpoint46h_pre, checkpoint46g_post
Changes since 1.3: +33 -4 lines
o Include a new diagnostic variable phiHydLow for the ocean model
  - in z-coordinates, it is the bottom pressure anomaly
  - in p-coordinates, it is the sea surface elevation
  - in both cases, these variable have global drift, reflecting the mass
    drift in z-coordinates and the volume drift in p-coordinates
  - included time averaging for phiHydLow, be aware of the drift!
o depth-dependent computation of Bo_surf for pressure coordinates
  in the ocean (buoyancyRelation='OCEANICP')
  - requires a new routine (FIND_RHO_SCALAR) to compute density with only
    Theta, Salinity, and Pressure in the parameter list. This routine is
    presently contained in find_rho.F. This routine does not give the
    correct density for 'POLY3', which would be a z-dependent reference
    density.
o cleaned up find_rho
  - removed obsolete 'eqn' from the parameter list.
o added two new verification experiments: gop and goz
  (4x4 degree global ocean, 15 layers in pressure and height coordinates)

1 mlosch 1.4 C $Header: /u/gcmpack/MITgcm/model/src/ini_linear_phisurf.F,v 1.3 2001/09/26 18:09:15 cnh Exp $
2 jmc 1.1 C $Name: $
3    
4     #include "CPP_OPTIONS.h"
5    
6 cnh 1.3 CBOP
7     C !ROUTINE: INI_LINEAR_PHISURF
8     C !INTERFACE:
9 jmc 1.1 SUBROUTINE INI_LINEAR_PHISURF( myThid )
10 cnh 1.3
11     C !DESCRIPTION: \bv
12     C *==========================================================*
13     C | SUBROUTINE INI_LINEAR_PHISURF
14     C | o Initialise the Linear Relation Phi_surf(eta)
15     C *==========================================================*
16     C | Presently: Initialise -Boyancy at surface level (Bo_surf)
17     C | to setup the Linear relation: Phi_surf(eta)=Bo_surf*eta
18     C | Futur: might add other things for Non-Linear FreeSurface
19     C *==========================================================*
20     C \ev
21    
22     C !USES:
23 jmc 1.1 IMPLICIT NONE
24     C === Global variables ===
25     #include "SIZE.h"
26     #include "EEPARAMS.h"
27     #include "PARAMS.h"
28     #include "GRID.h"
29     #include "SURFACE.h"
30    
31 cnh 1.3 C !INPUT/OUTPUT PARAMETERS:
32 jmc 1.1 C === Routine arguments ===
33     C myThid - Thread no. that called this routine.
34     INTEGER myThid
35    
36 cnh 1.3 C !LOCAL VARIABLES:
37 jmc 1.1 C === Local variables ===
38     C bi,bj - Loop counters
39     C I,J,K
40     CHARACTER*(MAX_LEN_MBUF) msgBuf
41     INTEGER bi, bj
42     INTEGER I, J, K
43 mlosch 1.4 _RL rhoLoc
44 jmc 1.1 _RL dPIdp
45 cnh 1.3 CEOP
46 jmc 1.1
47     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
48    
49     C-- Initialise -Boyancy at surface level : Bo_surf
50     C Bo_surf is defined as d/dr(Phi_surf) and set to g/rtoz (linear free surface)
51     C with rtoz = conversion factor from r-unit to z-unit (=horiVertRatio)
52     C an accurate formulation includes P_surf and T,S_surf effects on rho_surf:
53     C (setting uniformLin_PhiSurf=.FALSE.):
54     C z-ocean (rtoz=1) : Bo_surf = - Boyancy = gravity * rho_surf/rho_0
55     C p-atmos (rtoz=rho_c*g) : Bo_surf = (1/rho)_surf
56     C Note on Phi_surf splitting : Non-linear Time-dependent effects on b_surf
57     C [through eta & (T-tRef)_surf] are included in PhiHyd rather than in Bo_surf
58     C--
59     IF ( buoyancyRelation .eq. 'OCEANIC' ) THEN
60     C- gBaro = gravity (except for External mode test with reduced gravity)
61     DO bj=myByLo(myThid),myByHi(myThid)
62     DO bi=myBxLo(myThid),myBxHi(myThid)
63     DO J=1-Oly,sNy+Oly
64     DO I=1-Olx,sNx+Olx
65     Bo_surf(I,J,bi,bj) = gBaro
66     recip_Bo(I,J,bi,bj) = 1. _d 0 / gBaro
67     ENDDO
68     ENDDO
69     ENDDO
70     ENDDO
71     ELSEIF ( uniformLin_PhiSurf ) THEN
72     C- use a linear (in ps) uniform relation : Phi'_surf = 1/rhoConst * ps'_surf
73     DO bj=myByLo(myThid),myByHi(myThid)
74     DO bi=myBxLo(myThid),myBxHi(myThid)
75     DO J=1-Oly,sNy+Oly
76     DO I=1-Olx,sNx+Olx
77     Bo_surf(I,J,bi,bj) = recip_rhoConst
78     recip_Bo(I,J,bi,bj) = rhoConst
79     ENDDO
80     ENDDO
81     ENDDO
82     ENDDO
83 mlosch 1.4 ELSEIF ( buoyancyRelation .eq. 'OCEANICP' ) THEN
84     DO bj=myByLo(myThid),myByHi(myThid)
85     DO bi=myBxLo(myThid),myBxHi(myThid)
86     DO J=1-Oly,sNy+Oly
87     DO I=1-Olx,sNx+Olx
88     IF ( Ro_surf(I,J,bi,bj).GT.0. _d 0
89     & .AND. ksurfC(I,J,bi,bj).LE.Nr ) THEN
90     k = ksurfC(I,J,bi,bj)
91     CALL FIND_RHO_SCALAR(
92     & tRef(k), sRef(k), Ro_surf(I,J,bi,bj),
93     & rhoLoc, myThid )
94     if ( rhoLoc+rhoNil .eq. 0. _d 0 ) then
95     Bo_surf(I,J,bi,bj) = 0. _d 0
96     else
97     Bo_surf(I,J,bi,bj) = 1./(rhoLoc+rhoNil)
98     endif
99     recip_Bo(I,J,bi,bj) = rhoLoc+rhoNil
100     ELSE
101     Bo_surf(I,J,bi,bj) = 0. _d 0
102     recip_Bo(I,J,bi,bj) = 0. _d 0
103     ENDIF
104     ENDDO
105     ENDDO
106     ENDDO
107     ENDDO
108     ELSEIF ( buoyancyRelation .eq. 'ATMOSPHERIC' ) THEN
109 jmc 1.1 C- use a linearized (in ps) Non-uniform relation : Bo_surf(Po_surf,tRef_surf)
110     C--- Bo = d/d_p(Phi_surf) = tRef_surf*d/d_p(PI) ; PI = Cp*(p/Po)^kappa
111     DO bj=myByLo(myThid),myByHi(myThid)
112     DO bi=myBxLo(myThid),myBxHi(myThid)
113     DO J=1-Oly,sNy+Oly
114     DO I=1-Olx,sNx+Olx
115 jmc 1.2 IF ( Ro_surf(I,J,bi,bj).GT.0. _d 0
116     & .AND. ksurfC(I,J,bi,bj).LE.Nr ) THEN
117 jmc 1.1 dPIdp = (atm_cp*atm_kappa/atm_po)*
118     & (Ro_surf(I,J,bi,bj)/atm_po)**(atm_kappa-1. _d 0)
119 jmc 1.2 Bo_surf(I,J,bi,bj) = dPIdp*tRef(ksurfC(I,J,bi,bj))
120 jmc 1.1 recip_Bo(I,J,bi,bj) = 1. _d 0 / Bo_surf(I,J,bi,bj)
121     ELSE
122     Bo_surf(I,J,bi,bj) = 0.
123     recip_Bo(I,J,bi,bj) = 0.
124     ENDIF
125     ENDDO
126     ENDDO
127     ENDDO
128     ENDDO
129 mlosch 1.4 ELSE
130     STOP 'INI_LINEAR_PHISURF: We should never reach this point!'
131 jmc 1.1 ENDIF
132    
133     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
134    
135     C-- Update overlap regions
136     _EXCH_XY_R8(Bo_surf, myThid)
137     _EXCH_XY_R8(recip_Bo, myThid)
138    
139 mlosch 1.4 IF ( ( buoyancyRelation .eq. 'ATMOSPHERIC' .OR.
140     & buoyancyRelation .eq. 'OCEANICP' )
141     & .AND. .NOT.uniformLin_PhiSurf ) THEN
142 jmc 1.1 CALL WRITE_FLD_XY_RL( 'Bo_surf',' ',Bo_surf,0,myThid)
143     ENDIF
144    
145     RETURN
146     END

  ViewVC Help
Powered by ViewVC 1.1.22