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

Contents of /MITgcm/pkg/seaice/seaice_model.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 (21 years, 6 months ago) by heimbach
Branch: MAIN
CVS Tags: checkpoint46n_post, checkpoint47a_post, checkpoint47
Changes since 1.1: +101 -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 seaice_model( myTime, myIter, myThid )
7 C /==========================================================\
8 C | SUBROUTINE SEAICE_MODEL |
9 C | o Time stepping 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 "DYNVARS.h"
18 #include "PARAMS.h"
19 #include "FFIELDS.h"
20 #include "SEAICE.h"
21 #include "SEAICE_PARAMS.h"
22 #include "SEAICE_EXTERNAL.h"
23
24 C === Routine arguments ===
25 C myTime - Simulation time
26 C myIter - Simulation timestep number
27 C myThid - Thread no. that called this routine.
28 _RL myTime
29 INTEGER myIter
30 INTEGER myThid
31 CEndOfInterface
32
33 #ifdef ALLOW_SEAICE
34
35 C === Local variables ===
36 C i,j,k,bi,bj - Loop counters
37
38 INTEGER i, j, k, bi, bj
39
40 C--- Read wind, thermal, and evaporation minus precipitation if needed
41 CALL SEAICE_GET_FORCING ( myTime, myIter, myThid )
42
43 C-- Third level model velocity is used as proxy for geostrophic velocity
44 DO bj=myByLo(myThid),myByHi(myThid)
45 DO bi=myBxLo(myThid),myBxHi(myThid)
46 DO j=0,sNy+1
47 DO i=0,sNx+1
48 GWATX(I,J,bi,bj)=0.5*(uVel(i+1,j,3,bi,bj)
49 & +uVel(i+1,j+1,3,bi,bj))
50 GWATY(I,J,bi,bj)=0.5*(vVel(i,j+1,3,bi,bj)
51 & +vVel(i+1,j+1,3,bi,bj))
52 #ifdef SEAICE_DEBUG
53 c write(*,'(2i4,2i2,f7.1,7f12.3)')
54 c & ,i,j,bi,bj,UVM(I,J,bi,bj)
55 c & ,GWATX(I,J,bi,bj),GWATY(I,J,bi,bj)
56 c & ,uVel(i+1,j,3,bi,bj),uVel(i+1,j+1,3,bi,bj)
57 c & ,vVel(i,j+1,3,bi,bj),vVel(i+1,j+1,3,bi,bj)
58 #endif SEAICE_DEBUG
59 ENDDO
60 ENDDO
61 ENDDO
62 ENDDO
63
64 C solve ice momentum equations and calculate ocean surface stress
65 CALL DYNSOLVER ( myTime, myIter, myThid )
66
67 C NOW DO ADVECTION
68 CALL ADVECT( UICE, VICE, HEFF, HEFFM, myThid )
69 CALL ADVECT( UICE, VICE, AREA, HEFFM, myThid )
70
71 C NOW DO GROWTH
72 C MUST CALL GROWTH ONLY AFTER CALLING ADVECTION
73 CALL GROWTH( myTime, myIter, myThid)
74
75 C-- Update overlap regions for a bunch of stuff
76 _BARRIER
77 CALL EXCH_RL( HEFF, OLx, OLx, OLy, OLy, 3, OLx, OLy,
78 I FORWARD_SIMULATION, EXCH_UPDATE_CORNERS, myThid )
79 CALL EXCH_RL( AREA, OLx, OLx, OLy, OLy, 3, OLx, OLy,
80 I FORWARD_SIMULATION, EXCH_UPDATE_CORNERS, myThid )
81 _EXCH_XY_R4(fu , myThid )
82 _EXCH_XY_R4(fv , myThid )
83 _EXCH_XY_R4(EmPmR, myThid )
84 _EXCH_XY_R4(Qnet , myThid )
85 _EXCH_XY_R4(surfaceTendencyTice, myThid )
86 #ifdef SHORTWAVE_HEATING
87 _EXCH_XY_R4(Qsw , myThid )
88 #endif SHORTWAVE_HEATING
89 _EXCH_XYZ_R8(theta , myThid )
90
91 C-- Sea ice diagnostics.
92 CALL SEAICE_DO_DIAGS( myTime, myIter, myThid )
93
94 C-- Write sea ice restart files
95 CALL SEAICE_WRITE_PICKUP ( .FALSE.,
96 & myTime+deltaTClock, myIter+1, myThid )
97
98 #endif ALLOW_SEAICE
99
100 RETURN
101 END

  ViewVC Help
Powered by ViewVC 1.1.22