/[MITgcm]/MITgcm/pkg/seaice/seaice_init.F
ViewVC logotype

Annotation of /MITgcm/pkg/seaice/seaice_init.F

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


Revision 1.2 - (hide annotations) (download)
Tue Nov 12 20:47:27 2002 UTC (21 years, 7 months ago) by heimbach
Branch: MAIN
CVS Tags: checkpoint47a_post, checkpoint46n_post, checkpoint47
Changes since 1.1: +150 -0 lines
Merging from release1_p8 branch:
o New package: pkg/seaice
  Sea ice model by D. Menemenlis (JPL) and Jinlun Zhang (Seattle).
  The sea-ice code is based on Hibler (1979-1980).
  Two sea-ice dynamic solvers, ADI and LSR, are included.
  In addition to computing prognostic sea-ice variables and diagnosing
  the forcing/external data fields that drive the ocean model,
  SEAICE_MODEL also sets theta to the freezing point under sea-ice.
  The implied surface heat flux is then stored in variable
  surfaceTendencyTice, which is needed by KPP package (kpp_calc.F and
  kpp_transport_t.F) to diagnose surface buoyancy fluxes and for the
  non-local transport term.  Because this call precedes model
  thermodynamics, temperature under sea-ice may not be "exactly" at
  the freezing point by the time theta is dumped or time-averaged.

1 heimbach 1.2 C $Header:
2    
3     #include "SEAICE_OPTIONS.h"
4    
5     CStartOfInterface
6     SUBROUTINE SEAICE_INIT( myThid )
7     C /==========================================================\
8     C | SUBROUTINE SEAICE_INIT |
9     C | o Initialization of sea ice model. |
10     C |==========================================================|
11     C \==========================================================/
12     IMPLICIT NONE
13    
14     C === Global variables ===
15     #include "SIZE.h"
16     #include "EEPARAMS.h"
17     #include "PARAMS.h"
18     #include "GRID.h"
19     #include "SEAICE.h"
20     #include "SEAICE_GRID.h"
21     #include "SEAICE_DIAGS.h"
22     #include "SEAICE_PARAMS.h"
23     #include "SEAICE_EXTERNAL.h"
24    
25     C === Routine arguments ===
26     C myThid - Thread no. that called this routine.
27     INTEGER myThid
28     CEndOfInterface
29    
30     #ifdef ALLOW_SEAICE
31     C === Local variables ===
32     C i,j,k,bi,bj - Loop counters
33    
34     INTEGER i, j, k, bi, bj
35     _RS mask_uice
36     CHARACTER*(MAX_LEN_FNAM) fn
37    
38     #ifdef ALLOW_TIMEAVE
39     C Initialize averages to zero
40     DO bj = myByLo(myThid), myByHi(myThid)
41     DO bi = myBxLo(myThid), myBxHi(myThid)
42     CALL TIMEAVE_RESET(FUtave ,1,bi,bj,myThid)
43     CALL TIMEAVE_RESET(FVtave ,1,bi,bj,myThid)
44     CALL TIMEAVE_RESET(EmPmRtave,1,bi,bj,myThid)
45     CALL TIMEAVE_RESET(QNETtave ,1,bi,bj,myThid)
46     CALL TIMEAVE_RESET(QSWtave ,1,bi,bj,myThid)
47     CALL TIMEAVE_RESET(UICEtave ,1,bi,bj,myThid)
48     CALL TIMEAVE_RESET(VICEtave ,1,bi,bj,myThid)
49     CALL TIMEAVE_RESET(HEFFtave ,1,bi,bj,myThid)
50     CALL TIMEAVE_RESET(AREAtave ,1,bi,bj,myThid)
51     DO k=1,Nr
52     SEAICE_TimeAve(k,bi,bj)=0.
53     ENDDO
54     ENDDO
55     ENDDO
56     #endif /* ALLOW_TIMEAVE */
57    
58     C--- initialize grid info
59     DO bj=myByLo(myThid),myByHi(myThid)
60     DO bi=myBxLo(myThid),myBxHi(myThid)
61     DO J=1,sNy
62     DO I=1,sNx
63     TNGTICE(i,j,bi,bj)=tanPhiAtU(i,j,bi,bj)
64     TNGICE(i,j,bi,bj) =tanPhiAtV(i,j+1,bi,bj)
65     CSTICE(i,j,bi,bj) =cos(atan(tanPhiAtU(i,j,bi,bj)))
66     CSUICE(i,j,bi,bj) =cos(atan(tanPhiAtV(i,j+1,bi,bj)))
67     SINEICE(i,j,bi,bj)=sin(atan(tanPhiAtV(i,j+1,bi,bj)))
68     DXTICE(i,j,bi,bj)=dxF(i,j,bi,bj)/CSTICE(i,j,bi,bj)
69     DXUICE(i,j,bi,bj)=dxC(i+1,j,bi,bj)/CSUICE(i,j,bi,bj)
70     DYTICE(i,j,bi,bj)=dyF(i,j,bi,bj)
71     DYUICE(i,j,bi,bj)=dyC(i,j+1,bi,bj)
72     ENDDO
73     ENDDO
74     DO j=1-OLy,sNy+OLy
75     DO i=1-OLx,sNx+OLx
76     HEFFM(i,j,bi,bj)=1.0
77     IF (_hFacC(i,j,1,bi,bj).eq.0.) HEFFM(i,j,bi,bj)=0.0
78     ENDDO
79     ENDDO
80     DO J=1,sNy
81     DO I=1,sNx
82     UVM(i,j,bi,bj)=0.0
83     mask_uice=HEFFM(I,J, bi,bj)+HEFFM(I+1,J+1,bi,bj)
84     & +HEFFM(I,J+1,bi,bj)+HEFFM(I+1,J, bi,bj)
85     IF(mask_uice.GT.3.5) UVM(I,J,bi,bj)=1.0
86     ENDDO
87     ENDDO
88     DO j=1-OLy,sNy+OLy
89     DO i=1-OLx,sNx+OLx
90     TICE(I,J,bi,bj)=273.0 _d 0
91     UICEC(I,J,bi,bj)=0.0 _d 0
92     VICEC(I,J,bi,bj)=0.0 _d 0
93     AMASS(I,J,bi,bj)=1000.0
94     ENDDO
95     ENDDO
96     ENDDO
97     ENDDO
98    
99     C-- Update overlap regions
100     _EXCH_XY_R8(UVM, myThid)
101     _EXCH_XY_R8(TNGTICE, myThid)
102     _EXCH_XY_R8(TNGICE, myThid)
103     _EXCH_XY_R8(CSTICE, myThid)
104     _EXCH_XY_R8(CSUICE, myThid)
105     _EXCH_XY_R8(SINEICE, myThid)
106     _EXCH_XY_R8(DXTICE, myThid)
107     _EXCH_XY_R8(DXUICE, myThid)
108     _EXCH_XY_R8(DYTICE, myThid)
109     _EXCH_XY_R8(DYUICE, myThid)
110    
111     C-- Set model variables to initial/restart conditions
112     IF ( nIter0 .EQ. 0 ) THEN
113     DO bj=myByLo(myThid),myByHi(myThid)
114     DO bi=myBxLo(myThid),myBxHi(myThid)
115     DO j=1-OLy,sNy+OLy
116     DO i=1-OLx,sNx+OLx
117     HSNOW(I,J,bi,bj)=0.2 _d 0
118     YNEG(I,J,bi,bj)=0.0 _d 0
119     TMIX(I,J,bi,bj)=TICE(I,J,bi,bj)
120     DO k=1,3
121     HEFF(I,J,k,bi,bj)=1.0 _d 0
122     AREA(I,J,k,bi,bj)=HEFFM(i,j,bi,bj)
123     UICE(I,J,k,bi,bj)=0.0 _d 0
124     VICE(I,J,k,bi,bj)=0.0 _d 0
125     ENDDO
126     ENDDO
127     ENDDO
128     ENDDO
129     ENDDO
130     ELSE
131     CALL SEAICE_READ_PICKUP ( myThid )
132     ENDIF
133    
134     C--- Complete initialization
135     DO bj=myByLo(myThid),myByHi(myThid)
136     DO bi=myBxLo(myThid),myBxHi(myThid)
137     DO j=1-OLy,sNy+OLy
138     DO i=1-OLx,sNx+OLx
139     ZETA(I,J,bi,bj)=HEFF(I,J,1,bi,bj)*(1.0 _d 11)
140     ETA(I,J,bi,bj)=ZETA(I,J,bi,bj)/4.0
141     surfaceTendencyTice(i,j,bi,bj) = 0.0
142     ENDDO
143     ENDDO
144     ENDDO
145     ENDDO
146    
147     #endif ALLOW_SEAICE
148    
149     RETURN
150     END

  ViewVC Help
Powered by ViewVC 1.1.22