/[MITgcm]/MITgcm/pkg/obcs/obcs_init_variables.F
ViewVC logotype

Annotation of /MITgcm/pkg/obcs/obcs_init_variables.F

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


Revision 1.7 - (hide annotations) (download)
Mon Dec 15 20:22:20 2003 UTC (20 years, 6 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint52l_pre, hrcube4, hrcube5, checkpoint52j_pre, checkpoint52l_post, checkpoint52k_post, checkpoint54, checkpoint53, checkpoint52f_post, checkpoint52i_pre, hrcube_1, hrcube_2, hrcube_3, checkpoint52e_pre, checkpoint52e_post, checkpoint53d_post, checkpoint52m_post, checkpoint52f_pre, checkpoint54a_pre, checkpoint53c_post, checkpoint54a_post, checkpoint53a_post, checkpoint52d_post, checkpoint53g_post, checkpoint52i_post, checkpoint52h_pre, checkpoint53f_post, checkpoint52j_post, checkpoint52n_post, checkpoint53b_pre, checkpoint53b_post, checkpoint53d_pre
Changes since 1.6: +18 -1 lines
add a call to OBCS_READ_CHECKPOINT at the logical place and leave it
 commented for now.

1 jmc 1.7 C $Header: /u/gcmpack/MITgcm/pkg/obcs/obcs_init_variables.F,v 1.6 2002/02/08 22:16:09 jmc Exp $
2 adcroft 1.3 C $Name: $
3 adcroft 1.2
4     #include "OBCS_OPTIONS.h"
5    
6     SUBROUTINE OBCS_INIT_VARIABLES( myThid )
7     C /==========================================================\
8     C | SUBROUTINE OBCS_INIT_VARIABLES |
9     C | o Initialise OBCs variable data |
10     C |==========================================================|
11     C | |
12     C \==========================================================/
13     IMPLICIT NONE
14    
15     C === Global variables ===
16     #include "SIZE.h"
17     #include "EEPARAMS.h"
18     #include "PARAMS.h"
19     #include "DYNVARS.h"
20     #include "OBCS.h"
21    
22     C == Routine arguments ==
23     C myThid - Number of this instance of INI_DEPTHS
24     INTEGER myThid
25    
26     #ifdef ALLOW_OBCS
27    
28     C == Local variables ==
29     INTEGER bi, bj
30     INTEGER I, J, K
31 jmc 1.7 CHARACTER*(10) suff
32     INTEGER prec
33 adcroft 1.2
34     DO bj = myByLo(myThid), myByHi(myThid)
35     DO bi = myBxLo(myThid), myBxHi(myThid)
36    
37     DO K=1,Nr
38     DO I=1-Olx,sNx+Olx
39     OBNu(I,K,bi,bj)=0.
40     OBNv(I,K,bi,bj)=0.
41     OBNt(I,K,bi,bj)=0.
42 adcroft 1.4 OBNs(I,K,bi,bj)=0.
43 adcroft 1.2 OBSu(I,K,bi,bj)=0.
44     OBSv(I,K,bi,bj)=0.
45     OBSt(I,K,bi,bj)=0.
46 adcroft 1.4 OBSs(I,K,bi,bj)=0.
47 adcroft 1.2 #ifdef ALLOW_NONHYDROSTATIC
48     OBNw(I,K,bi,bj)=0.
49     OBSw(I,K,bi,bj)=0.
50     #endif
51     ENDDO
52     DO J=1-Oly,sNy+Oly
53     OBEu(J,K,bi,bj)=0.
54     OBEv(J,K,bi,bj)=0.
55     OBEt(J,K,bi,bj)=0.
56 adcroft 1.4 OBEs(J,K,bi,bj)=0.
57 adcroft 1.2 OBWu(J,K,bi,bj)=0.
58     OBWv(J,K,bi,bj)=0.
59     OBWt(J,K,bi,bj)=0.
60 adcroft 1.4 OBWs(J,K,bi,bj)=0.
61 adcroft 1.2 #ifdef ALLOW_NONHYDROSTATIC
62     OBEw(J,K,bi,bj)=0.
63     OBWw(J,K,bi,bj)=0.
64     #endif
65     ENDDO
66     ENDDO
67 jmc 1.5
68     #ifdef NONLIN_FRSURF
69     DO I=1-Olx,sNx+Olx
70     OBNeta(I,bi,bj)=0.
71     OBSeta(I,bi,bj)=0.
72     ENDDO
73     DO J=1-Oly,sNy+Oly
74     OBEeta(J,bi,bj)=0.
75     OBWeta(J,bi,bj)=0.
76     ENDDO
77     #endif /* NONLIN_FRSURF */
78 adcroft 1.2
79     #ifdef ALLOW_ORLANSKI
80     IF (useOrlanskiNorth.OR.useOrlanskiSouth.OR.
81     & useOrlanskiEast.OR.useOrlanskiWest) THEN
82     CALL ORLANSKI_INIT(bi, bj, myThid)
83     ENDIF
84     #endif /* ALLOW_ORLANSKI */
85 adcroft 1.3
86     ENDDO
87     ENDDO
88 jmc 1.7
89     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
90     C jmc: here is the logical place to read OBCS-pickup files
91     C but a) without Orlanski: pass the test 1+1=2 without reading pickup.
92     C b) with Orlanski: 1+1=2 fail even with this bit of code
93     IF ( nIter0.NE.0 ) THEN
94     prec = precFloat64
95     IF (pickupSuff.EQ.' ') THEN
96     WRITE(suff,'(I10.10)') nIter0
97     ELSE
98     WRITE(suff,'(A10)') pickupSuff
99     ENDIF
100     c CALL OBCS_READ_CHECKPOINT(prec, nIter0, suff, myThid)
101     ENDIF
102     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
103 adcroft 1.2
104     C-- Apply OBCS values to initial conditions for consistancy
105     DO bj = myByLo(myThid), myByHi(myThid)
106     DO bi = myBxLo(myThid), myBxHi(myThid)
107 jmc 1.6 CALL OBCS_CALC( bi, bj, startTime, nIter0,
108 adcroft 1.2 & uVel, vVel, wVel, theta, salt, myThid )
109     DO K=1,Nr
110     CALL OBCS_APPLY_UV( bi, bj, k, uVel, vVel, myThid )
111     CALL OBCS_APPLY_TS( bi, bj, k, theta, salt, myThid )
112     ENDDO
113     ENDDO
114     ENDDO
115    
116     #endif /* ALLOW_OBCS */
117     RETURN
118     END

  ViewVC Help
Powered by ViewVC 1.1.22