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

Contents of /MITgcm/pkg/seaice/groatb.F

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


Revision 1.2 - (show annotations) (download)
Tue Nov 12 20:47:27 2002 UTC (22 years, 8 months ago) by heimbach
Branch: MAIN
CVS Tags: checkpoint47, checkpoint47a_post, checkpoint46n_post
Changes since 1.1: +92 -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 C $Header:
2
3 #include "SEAICE_OPTIONS.h"
4
5 CStartOfInterface
6 SUBROUTINE groatb( A22, myThid )
7 C /==========================================================\
8 C | SUBROUTINE groatb |
9 C | o Calculate ice growth |
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 "DYNVARS.h"
19 #include "FFIELDS.h"
20 #include "SEAICE.h"
21 #include "SEAICE_FFIELDS.h"
22
23 C === Routine arguments ===
24 C myThid - Thread no. that called this routine.
25 _RL A22
26 INTEGER myThid
27 CEndOfInterface
28
29 #ifdef ALLOW_SEAICE
30
31 C === Local variables ===
32 C i,j,k,bi,bj - Loop counters
33
34 INTEGER i, j, k, bi, bj
35 INTEGER KOPEN
36 _RL U1, V1
37
38 _RL HICE (1-OLx:sNx+OLx, 1-OLy:sNy+OLy)
39 _RL AR (1-OLx:sNx+OLx, 1-OLy:sNy+OLy)
40 _RL UG (1-OLx:sNx+OLx, 1-OLy:sNy+OLy)
41
42 C if this is not done before then do it here
43 _EXCH_XY_R8(GAIRX, myThid)
44 _EXCH_XY_R8(GAIRY, myThid)
45
46 DO bj=myByLo(myThid),myByHi(myThid)
47 DO bi=myBxLo(myThid),myBxHi(myThid)
48
49 C DETERMINE AMOUNT OF OPEN WATER AND ICE THICKNESS
50 DO J=1,sNy
51 DO I=1,sNx
52 AREA(I,J,2,bi,bj)=MAX(A22,AREA(I,J,2,bi,bj))
53 FHEFF(I,J,bi,bj)=0.0
54 HICE(I,J)=HEFF(I,J,2,bi,bj)/AREA(I,J,2,bi,bj)
55 ENDDO
56 ENDDO
57
58 C NOW DETERMINE MIXED LAYER TEMPERATURE
59 DO J=1,sNy
60 DO I=1,sNx
61 TMIX(I,J,bi,bj)=theta(I,J,1,bi,bj)+273.16E+00
62 #ifdef SEAICE_DEBUG
63 TMIX(I,J,bi,bj)=MAX(TMIX(I,J,bi,bj),271.2E+00)
64 #endif SEAICE_DEBUG
65 ENDDO
66 ENDDO
67
68 DO J=1,sNy
69 DO I=1,sNx
70 U1=0.25*(GAIRX(I-1,J-1,bi,bj)+GAIRX(I-1,J,bi,bj)
71 1 +GAIRX(I,J-1,bi,bj)+GAIRX(I,J,bi,bj))
72 V1=0.25*(GAIRY(I-1,J-1,bi,bj)+GAIRY(I-1,J,bi,bj)
73 1 +GAIRY(I,J-1,bi,bj)+GAIRY(I,J,bi,bj))
74 UG(I,J)=SQRT(U1**2+V1**2)
75 ENDDO
76 ENDDO
77
78 C NOW DETERMINE GROWTH RATES
79 C FIRST DO OPEN WATER
80 KOPEN=-1
81 CALL BUDGET(UG, TMIX, HICE, FO, KOPEN, bi, bj)
82 C NOW DO ICE
83 KOPEN=1
84 CALL BUDGET(UG, TICE, HICE, FICE, KOPEN, bi, bj)
85
86 ENDDO
87 ENDDO
88
89 #endif ALLOW_SEAICE
90
91 RETURN
92 END

  ViewVC Help
Powered by ViewVC 1.1.22