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

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

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


Revision 1.2 - (hide annotations) (download)
Sat May 1 16:57:07 2010 UTC (14 years, 1 month ago) by jmc
Branch: MAIN
CVS Tags: checkpoint63h, checkpoint63i, checkpoint63j, checkpoint63k, checkpoint63d, checkpoint63e, checkpoint63f, checkpoint63g, checkpoint63a, checkpoint63b, checkpoint63c, checkpoint63, checkpoint62g, checkpoint62k, checkpoint62j, checkpoint62i, checkpoint62h, checkpoint62o, checkpoint62n, checkpoint62m, checkpoint62l, checkpoint62s, checkpoint62r, checkpoint62q, checkpoint62p, checkpoint62w, checkpoint62v, checkpoint62u, checkpoint62t, checkpoint62z, checkpoint62y, checkpoint62x
Changes since 1.1: +6 -2 lines
replace "write(0,*)" with call to PRINT_MESSAGE

1 jmc 1.2 C $Header: /u/gcmpack/MITgcm/model/src/ini_nh_fields.F,v 1.1 2009/12/11 13:56:28 jmc Exp $
2 jmc 1.1 C $Name: $
3    
4     #include "CPP_OPTIONS.h"
5    
6     CBOP
7     C !ROUTINE: INI_NH_FIELDS
8     C !INTERFACE:
9     SUBROUTINE INI_NH_FIELDS( myThid )
10    
11     C !DESCRIPTION: \bv
12     C *==========================================================*
13     C | SUBROUTINE INI_NH_FIELDS
14     C | o Set model initial non-hydrostatic fields.
15     C *==========================================================*
16     C | Note: If using NH form,
17     C | call this S/R whether starting or restarting simulation.
18     C | This is different from other "true" ini_fields type S/R
19     C | (e.g., INI_VEL) which are called only when starting.
20     C | Reason: no real physical field to initialise (since wVel
21     C | is diagnose from continuity) but needs to set few arrays
22     C *==========================================================*
23     C \ev
24    
25     C !USES:
26     IMPLICIT NONE
27     C === Global variables ===
28     #include "SIZE.h"
29     #include "EEPARAMS.h"
30     #include "PARAMS.h"
31     #include "GRID.h"
32     #include "RESTART.h"
33     #include "NH_VARS.h"
34    
35     C !INPUT/OUTPUT PARAMETERS:
36     C == Routine arguments ==
37     C myThid :: My Thread Id number
38     INTEGER myThid
39    
40     #ifdef ALLOW_NONHYDROSTATIC
41     C !LOCAL VARIABLES:
42     C == Local variables ==
43     INTEGER bi,bj
44     INTEGER i,j,k
45     INTEGER ks
46 jmc 1.2 CHARACTER*(MAX_LEN_MBUF) msgBuf
47 jmc 1.1 CEOP
48    
49     IF ( startTime .EQ. baseTime .AND. nIter0 .EQ. 0
50     & .AND. pickupSuff .EQ. ' ' ) THEN
51     C-- Case where starting from initial conditions
52    
53     C-- Read an initial non-hydrostatic pressure field
54     c IF (phiNHinitFile .NE. ' ') THEN
55     c CALL READ_FLD_XYZ_RL( phiNHinitFile, ' ', phi_nh, 0, myThid )
56     c _EXCH_XYZ_RL(phi_nh, myThid)
57     c ENDIF
58    
59     ELSE
60     C-- Case where restarting from a pickup
61    
62 jmc 1.2 WRITE(msgBuf,'(A,I4)')
63     & 'INI_NH_FIELDS: dPhiNHstatus=', dPhiNHstatus
64     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
65     & SQUEEZE_RIGHT, myThid )
66 jmc 1.1 IF ( exactConserv .AND. dPhiNHstatus.EQ.0 ) THEN
67     c IF ( exactConserv ) THEN
68     C-- Separate the Hydrostatic Surface Pressure adjusment (=> put it in dPhiNH)
69     C from the Non-hydrostatic pressure (since cg3d_x contains both contribution)
70     DO bj=myByLo(myThid),myByHi(myThid)
71     DO bi=myBxLo(myThid),myBxHi(myThid)
72     IF ( select_rStar.EQ.0 .AND. usingZCoords ) THEN
73     C- Z coordinate: assume surface @ level k=1
74     DO j=1-OLy,sNy+OLy
75     DO i=1-OLx,sNx+OLx
76     dPhiNH(i,j,bi,bj) = phi_nh(i,j,1,bi,bj)
77     c dPhiNH(i,j,bi,bj) = 0.
78     ENDDO
79     ENDDO
80     ELSEIF ( select_rStar.EQ.0 ) THEN
81     C- Other than Z coordinate: no assumption on surface level index
82     DO j=1-OLy,sNy+OLy
83     DO i=1-OLx,sNx+OLx
84     ks = ksurfC(i,j,bi,bj)
85     IF ( ks.LE.Nr ) THEN
86     dPhiNH(i,j,bi,bj) = phi_nh(i,j,ks,bi,bj)
87     ELSE
88     dPhiNH(i,j,bi,bj) = 0.
89     ENDIF
90     ENDDO
91     ENDDO
92     #ifdef NONLIN_FRSURF
93     ELSE
94     C rStar : take vertical average of P_NH as Hyd.Surf.Press adjustment
95     DO j=1-OLy,sNy+OLy
96     DO i=1-OLx,sNx+OLx
97     dPhiNH(i,j,bi,bj) = 0.
98     ENDDO
99     ENDDO
100     DO k=1,Nr
101     DO j=1-OLy,sNy+OLy
102     DO i=1-OLx,sNx+OLx
103     dPhiNH(i,j,bi,bj) = dPhiNH(i,j,bi,bj)
104     & + phi_nh(i,j,k,bi,bj)*drF(k)*hFacC(i,j,k,bi,bj)
105     ENDDO
106     ENDDO
107     ENDDO
108     DO j=1-OLy,sNy+OLy
109     DO i=1-OLx,sNx+OLx
110     dPhiNH(i,j,bi,bj) = dPhiNH(i,j,bi,bj)
111     & *recip_Rcol(i,j,bi,bj)
112     ENDDO
113     ENDDO
114     #endif /* NONLIN_FRSURF */
115     ENDIF
116     ENDDO
117     ENDDO
118     C- end of if-block: dPhiNH_status
119     ENDIF
120    
121     ENDIF
122    
123     C-- Set the variable viscosities to default value.
124     DO bj = myByLo(myThid), myByHi(myThid)
125     DO bi = myBxLo(myThid), myBxHi(myThid)
126     DO k = 1,Nr
127     DO j=1-Oly,sNy+Oly
128     DO i=1-Olx,sNx+Olx
129     viscAh_W(i,j,k,bi,bj) = viscAhW
130     viscA4_W(i,j,k,bi,bj) = viscA4W
131     ENDDO
132     ENDDO
133     ENDDO
134     ENDDO
135     ENDDO
136    
137     #endif /* ALLOW_NONHYDROSTATIC */
138     RETURN
139     END

  ViewVC Help
Powered by ViewVC 1.1.22