/[MITgcm]/MITgcm/pkg/icefront/icefront_init_fixed.F
ViewVC logotype

Contents of /MITgcm/pkg/icefront/icefront_init_fixed.F

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


Revision 1.4 - (show annotations) (download)
Wed Mar 24 22:03:35 2010 UTC (14 years, 2 months ago) by yunx
Branch: MAIN
CVS Tags: checkpoint63d, checkpoint63e, checkpoint63f, checkpoint63g, checkpoint63a, checkpoint63b, checkpoint63c, checkpoint63, checkpoint62g, checkpoint62f, checkpoint62e, checkpoint62k, checkpoint62j, checkpoint62i, checkpoint62h, checkpoint62o, checkpoint62n, checkpoint62m, checkpoint62l, checkpoint62s, checkpoint62r, checkpoint62q, checkpoint62p, checkpoint62w, checkpoint62v, checkpoint62u, checkpoint62t, checkpoint62z, checkpoint62y, checkpoint62x
Changes since 1.3: +13 -2 lines
Adding ABS around R_icefront to make sure depth is positive.

1 C $Header: /u/gcmpack/MITgcm/pkg/icefront/icefront_init_fixed.F,v 1.3 2010/01/29 01:05:27 dimitri Exp $
2 C $Name: $
3
4 #include "ICEFRONT_OPTIONS.h"
5
6 SUBROUTINE ICEFRONT_INIT_FIXED( myThid )
7 C *============================================================*
8 C | SUBROUTINE ICEFRONT_INIT_FIXED
9 C | o Routine to initialize ICEFRONT parameters and variables.
10 C *============================================================*
11 C | Initialize ICEFRONT parameters and variables.
12 C *============================================================*
13 IMPLICIT NONE
14
15 C === Global variables ===
16 #include "SIZE.h"
17 #include "EEPARAMS.h"
18 #include "PARAMS.h"
19 #include "GRID.h"
20 #include "ICEFRONT.h"
21
22 C === Routine arguments ===
23 C myThid - Number of this instance of ICEFRONT_INIT_FIXED
24 INTEGER myThid
25
26 #ifdef ALLOW_ICEFRONT
27 C === Local variables ===
28 C I,J,K,bi,bj - Loop counters
29 INTEGER I, J, K, bi, bj
30 INTEGER ISinterface
31
32 IF ( ICEFRONTlengthFile .NE. ' ' ) THEN
33 CALL READ_FLD_XY_RS( ICEFRONTlengthFile, ' ',
34 & icefrontlength, 0, myThid )
35 _EXCH_XY_RS( icefrontlength, myThid )
36 ENDIF
37
38 IF ( ICEFRONTdepthFile .NE. ' ' ) THEN
39 _BARRIER
40 CALL READ_FLD_XY_RS( ICEFRONTdepthFile, ' ',
41 & R_icefront, 0, myThid )
42 _EXCH_XY_RS( R_icefront, myThid )
43 ENDIF
44
45 C Make sure that R_icefront is positive
46 DO bj = myByLo(myThid), myByHi(myThid)
47 DO bi = myBxLo(myThid), myBxHi(myThid)
48 DO J = 1-OLy, sNy+OLy
49 DO I = 1-OLx, sNx+OLx
50 R_icefront(I,J,bi,bj) = ABS(R_icefront(I,J,bi,bj))
51 ENDDO
52 ENDDO
53 ENDDO
54 ENDDO
55
56 DO bj = myByLo(myThid), myByHi(myThid)
57 DO bi = myBxLo(myThid), myBxHi(myThid)
58 DO J = 1-OLy, sNy+OLy
59 DO I = 1-OLx, sNx+OLx
60 K_icefront(i,j,bi,bj) = 0
61 DO K = 1 , Nr
62 IF ( R_icefront(I,J,bi,bj) .GT. ABS(rF(K)))
63 & K_icefront(I,J,bi,bj) = K
64 ENDDO
65 ENDDO
66 ENDDO
67 ENDDO
68 ENDDO
69
70 #undef ALLOW_ICEFRONT_DEBUG
71 #ifdef ALLOW_ICEFRONT_DEBUG
72 DO bj = myByLo(myThid), myByHi(myThid)
73 DO bi = myBxLo(myThid), myBxHi(myThid)
74 DO J = 1, sNy
75 DO I = 1, sNx
76 C IsInterface=0
77 IF (ICEFRONTlength(I,J,bi,bj) .GT. 0. _d 0) THEN
78 C print*, 'IsInterface=', '2' , ',xuyun'
79 IsInterface=Isinterface + K_icefront(I,J,bi,bj)
80 ENDIF
81 ENDDO
82 ENDDO
83 ENDDO
84 ENDDO
85 print*, 'Interface # =', IsInterface
86 #endif /* ALLOW_ICEFRONT_DEBUG */
87
88 #ifdef ALLOW_DIAGNOSTICS
89 IF ( useDiagnostics ) THEN
90 CALL ICEFRONT_DIAGNOSTICS_INIT(myThid)
91 ENDIF
92 #endif /* ALLOW_DIAGNOSTICS */
93 #endif /* ALLOW_ICEFRONT */
94
95 RETURN
96 END

  ViewVC Help
Powered by ViewVC 1.1.22