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

Diff of /MITgcm/pkg/seaice/seaice_model.F

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

revision 1.13 by dimitri, Thu Nov 13 06:35:15 2003 UTC revision 1.25 by dimitri, Mon Dec 27 20:34:11 2004 UTC
# Line 3  C $Name$ Line 3  C $Name$
3    
4  #include "SEAICE_OPTIONS.h"  #include "SEAICE_OPTIONS.h"
5    
6  CStartOfInterface  CBOP
7    C !ROUTINE: SEAICE_MODEL
8    
9    C !INTERFACE: ==========================================================
10        SUBROUTINE seaice_model( myTime, myIter, myThid )        SUBROUTINE seaice_model( myTime, myIter, myThid )
11    
12    C !DESCRIPTION: \bv
13  C     /===========================================================\  C     /===========================================================\
14  C     | SUBROUTINE SEAICE_MODEL                                   |  C     | SUBROUTINE SEAICE_MODEL                                   |
15  C     | o Time stepping of a dynamic/thermodynamic sea ice model. |  C     | o Time stepping of a dynamic/thermodynamic sea ice model. |
16  C     |  Dynamics solver: Zhang/Hibler, JGR, 102, 8691-8702, 1997 |  C     |  Dynamics solver: Zhang/Hibler, JGR, 102, 8691-8702, 1997 |
 C     |    and          Zhang/Rothrock, JGR, 105, 3325-3338, 2000 |  
17  C     |  Thermodynamics:        Hibler, MWR, 108, 1943-1973, 1980 |  C     |  Thermodynamics:        Hibler, MWR, 108, 1943-1973, 1980 |
18  C     |  Rheology:              Hibler, JPO,   9,  815- 846, 1979 |  C     |  Rheology:              Hibler, JPO,   9,  815- 846, 1979 |
19  C     |  Snow:          Zhang et al.  , JPO,  28,  191- 217, 1998 |  C     |  Snow:          Zhang et al.  , JPO,  28,  191- 217, 1998 |
# Line 19  C     |  zhang@apl.washington.edu / mene Line 23  C     |  zhang@apl.washington.edu / mene
23  C     |===========================================================|  C     |===========================================================|
24  C     \===========================================================/  C     \===========================================================/
25        IMPLICIT NONE        IMPLICIT NONE
26    c \ev
27    
28    C !USES: ===============================================================
29  C     === Global variables ===  C     === Global variables ===
30  #include "SIZE.h"  #include "SIZE.h"
31  #include "EEPARAMS.h"  #include "EEPARAMS.h"
32  #include "DYNVARS.h"  #include "DYNVARS.h"
33  #include "PARAMS.h"  #include "PARAMS.h"
34    #include "GRID.h"
35  #include "FFIELDS.h"  #include "FFIELDS.h"
36  #include "SEAICE.h"  #include "SEAICE.h"
37  #include "SEAICE_PARAMS.h"  #include "SEAICE_PARAMS.h"
# Line 37  C     === Global variables === Line 44  C     === Global variables ===
44  # include "tamc.h"  # include "tamc.h"
45  #endif  #endif
46    
47    C !INPUT PARAMETERS: ===================================================
48  C     === Routine arguments ===  C     === Routine arguments ===
49  C     myTime - Simulation time  C     myTime - Simulation time
50  C     myIter - Simulation timestep number  C     myIter - Simulation timestep number
# Line 46  C     myThid - Thread no. that called th Line 54  C     myThid - Thread no. that called th
54        INTEGER myThid        INTEGER myThid
55  CEndOfInterface  CEndOfInterface
56    
57  #ifdef ALLOW_SEAICE  C !LOCAL VARIABLES: ====================================================
   
58  C     === Local variables ===  C     === Local variables ===
59  C     i,j,bi,bj - Loop counters  C     i,j,bi,bj - Loop counters
   
60        INTEGER i, j, bi, bj        INTEGER i, j, bi, bj
61          LOGICAL  DIFFERENT_MULTIPLE
62          EXTERNAL DIFFERENT_MULTIPLE
63    CEOP
64    
65  #ifdef SEAICE_EXTERNAL_FORCING  #ifdef SEAICE_EXTERNAL_FORCING
66  C--   Atmospheric state and runoff are from  C--   Atmospheric state and runoff are from
67  C     pkg/exf, which does not update edges.  C     pkg/exf, which does not update edges.
68           _EXCH_XY_R8( uwind,  myThid )        CALL EXCH_UV_XY_RL(uwind,vwind,.TRUE.,myThid)
69           _EXCH_XY_R8( vwind,  myThid )        _EXCH_XY_R8( atemp,  myThid )
70           _EXCH_XY_R8( atemp,  myThid )        _EXCH_XY_R8( aqh,    myThid )
71           _EXCH_XY_R8( aqh,    myThid )        _EXCH_XY_R8( lwdown, myThid )
72           _EXCH_XY_R8( lwdown, myThid )        _EXCH_XY_R8( swdown, mythid )
73           _EXCH_XY_R8( swdown, mythid )        _EXCH_XY_R8( precip, myThid )
74           _EXCH_XY_R8( precip, myThid )        _EXCH_XY_R8( evap,   myThid )
75           _EXCH_XY_R8( evap,   myThid )        _EXCH_XY_R8( runoff, myThid )
          _EXCH_XY_R8( runoff, myThid )  
76  #else /* SEAICE_EXTERNAL_FORCING */  #else /* SEAICE_EXTERNAL_FORCING */
77  C--   Load atmospheric state and runoff.  C--   Load atmospheric state and runoff.
78        CALL SEAICE_GET_FORCING ( myTime, myIter, myThid )        CALL SEAICE_GET_FORCING ( myTime, myIter, myThid )
79  #endif /* SEAICE_EXTERNAL_FORCING */  #endif /* SEAICE_EXTERNAL_FORCING */
80    
81  C--   Third level model velocity is used as proxy for geostrophic velocity  C--   Compute proxy for geostrophic velocity,
82        DO bj=myByLo(myThid),myByHi(myThid)        DO bj=myByLo(myThid),myByHi(myThid)
83         DO bi=myBxLo(myThid),myBxHi(myThid)         DO bi=myBxLo(myThid),myBxHi(myThid)
84          DO j=0,sNy+1          DO j=0,sNy+1
85           DO i=0,sNx+1           DO i=0,sNx+1
86            GWATX(I,J,bi,bj)=HALF*(uVel(i,j,3,bi,bj)            GWATX(I,J,bi,bj)=HALF*(uVel(i,j,KGEO(I,J,bi,bj),bi,bj)
87       &                         +uVel(i,j-1,3,bi,bj))       &                         +uVel(i,j-1,KGEO(I,J,bi,bj),bi,bj))
88            GWATY(I,J,bi,bj)=HALF*(vVel(i,j,3,bi,bj)            GWATY(I,J,bi,bj)=HALF*(vVel(i,j,KGEO(I,J,bi,bj),bi,bj)
89       &                         +vVel(i-1,j,3,bi,bj))       &                         +vVel(i-1,j,KGEO(I,J,bi,bj),bi,bj))
90  #ifdef SEAICE_DEBUG  #ifdef SEAICE_DEBUG
91  c          write(*,'(2i4,2i2,f7.1,7f12.3)')  c          write(*,'(2i4,2i2,f7.1,7f12.3)')
92  c     &     ,i,j,bi,bj,UVM(I,J,bi,bj)  c     &     ,i,j,bi,bj,UVM(I,J,bi,bj)
# Line 101  CADJ STORE area  = comlev1, key = ikey_d Line 109  CADJ STORE area  = comlev1, key = ikey_d
109  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
110    
111  C solve ice momentum equations and calculate ocean surface stress  C solve ice momentum equations and calculate ocean surface stress
112        CALL DYNSOLVER ( myTime, myIter, myThid )        IF ( DIFFERENT_MULTIPLE(
113         &     SEAICE_deltaTdyn,myTime,myTime-SEAICE_deltaTtherm) ) THEN
114             CALL TIMER_START('DYNSOLVER          [SEAICE_MODEL]',myThid)
115             CALL DYNSOLVER ( myTime, myIter, myThid )
116             CALL TIMER_STOP ('DYNSOLVER          [SEAICE_MODEL]',myThid)
117          ENDIF
118    
119  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
120  # ifdef SEAICE_ALLOW_DYNAMICS  # ifdef SEAICE_ALLOW_DYNAMICS
# Line 120  C     MUST CALL GROWTH ONLY AFTER CALLIN Line 133  C     MUST CALL GROWTH ONLY AFTER CALLIN
133        CALL GROWTH( myTime, myIter, myThid)        CALL GROWTH( myTime, myIter, myThid)
134    
135  C--   Update overlap regions for a bunch of stuff  C--   Update overlap regions for a bunch of stuff
136         _BARRIER        _BARRIER
137         CALL SEAICE_EXCH( HEFF, myThid )        CALL SEAICE_EXCH( HEFF, myThid )
138         CALL SEAICE_EXCH( AREA, myThid )        CALL SEAICE_EXCH( AREA, myThid )
139         _EXCH_XY_R4(fu   , myThid )        CALL EXCH_UV_XY_RS(fu,fv,.TRUE.,myThid)
140         _EXCH_XY_R4(fv   , myThid )        _EXCH_XY_R4(EmPmR, myThid )
141         _EXCH_XY_R4(EmPmR, myThid )        _EXCH_XY_R4(Qnet , myThid )
        _EXCH_XY_R4(Qnet , myThid )  
        _EXCH_XY_R4(surfaceTendencyTice, myThid )  
142  #ifdef SHORTWAVE_HEATING  #ifdef SHORTWAVE_HEATING
143         _EXCH_XY_R4(Qsw  , myThid )        _EXCH_XY_R4(Qsw  , myThid )
144  #endif  #endif
145         _EXCH_XYZ_R8(theta , myThid )        _EXCH_XYZ_R8(theta , myThid )
146    
147  C--   Sea ice diagnostics.  C--   Sea ice diagnostics.
148        CALL SEAICE_DO_DIAGS( myTime, myIter, myThid )  C     <= moved to S/R do_the_model_io with other pkgs
149    
150  C--   Write sea ice restart files  C--   Write sea ice restart files
151        CALL SEAICE_WRITE_PICKUP ( .FALSE.,  C     <= moved to S/R packages_write_pickup with other pkgs
      &     myTime+deltaTClock, myIter+1, myThid )  
152    
153  C---------------------------------------------------  C---------------------------------------------------
154  C OOH NOOOO we need to move the whole stuff  C OOH NOOOO we need to move the whole stuff
# Line 150  CRG CADJ store UICE,VICE,AREA,HEFF,fu,fv Line 160  CRG CADJ store UICE,VICE,AREA,HEFF,fu,fv
160  C--   Call sea-ice cost function routine  C--   Call sea-ice cost function routine
161  CRG      CALL SEAICE_COST( myTime, myIter, myThid )  CRG      CALL SEAICE_COST( myTime, myIter, myThid )
162    
 #endif /* ALLOW_SEAICE */  
   
163        RETURN        RETURN
164        END        END

Legend:
Removed from v.1.13  
changed lines
  Added in v.1.25

  ViewVC Help
Powered by ViewVC 1.1.22