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

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

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


Revision 1.2 - (hide annotations) (download)
Wed Mar 15 19:49:04 2006 UTC (18 years, 1 month ago) by mlosch
Branch: MAIN
CVS Tags: checkpoint58d_post, checkpoint58c_post
Changes since 1.1: +31 -1 lines
  - added a few comments to seaice_diffusion.F
  - separate C-grid and B-grid versions more cleanly (UVM and seaiceMaskU/V
    are now exclusive)
  - add a new ocean-ice stress coupling method (Hibler and Bryan, 1987) which
    required re-ordering the code a little:
   + make DAIRN global variable (defined in SEAICE)
   + move computation of the viscosities eta and zeta into a new separate
     routine (because I need to recompute them in seaice_ocean_stress.F)

1 mlosch 1.2 C $Header: /u/gcmpack/MITgcm/pkg/seaice/seaice_diffusion.F,v 1.1 2006/02/16 10:41:48 mlosch Exp $
2 mlosch 1.1 C $Name: $
3    
4     #include "SEAICE_OPTIONS.h"
5    
6     CStartOfInterface
7     SUBROUTINE SEAICE_DIFFUSION(
8     U HEFF,
9     I HEFFM, DELTT, myTime, myIter, myThid )
10     C /==========================================================\
11     C | SUBROUTINE advect |
12     C | o Calculate ice advection |
13     C |==========================================================|
14     C \==========================================================/
15     IMPLICIT NONE
16    
17     C === Global variables ===
18     #include "SIZE.h"
19     #include "EEPARAMS.h"
20     #include "PARAMS.h"
21     #include "GRID.h"
22     #include "SEAICE_PARAMS.h"
23     CML#include "SEAICE_GRID.h"
24    
25     #ifdef ALLOW_AUTODIFF_TAMC
26     # include "tamc.h"
27     #endif
28    
29     C === Routine arguments ===
30     C myThid - Thread no. that called this routine.
31     _RL HEFF (1-OLx:sNx+OLx,1-OLy:sNy+OLy,3,nSx,nSy)
32     _RL HEFFM (1-OLx:sNx+OLx,1-OLy:sNy+OLy, nSx,nSy)
33     _RL DELTT
34     _RL myTime
35     INTEGER myIter
36     INTEGER myThid
37     CEndOfInterface
38    
39     C === Local variables ===
40     C i,j,k,bi,bj - Loop counters
41    
42     INTEGER i, j, bi, bj
43    
44     _RL DIFFA(1-OLx:sNx+OLx, 1-OLy:sNy+OLy,nSx,nSy)
45    
46     #ifdef ALLOW_AUTODIFF_TAMC
47     CADJ STORE heff = comlev1, key = ikey_dynamics
48     #endif /* ALLOW_AUTODIFF_TAMC */
49    
50    
51 mlosch 1.2 C-- This would be the natural way to do diffusion (explicitly)
52     C For now we stick to the modified Eulerian time step
53     CML DO bj=myByLo(myThid),myByHi(myThid)
54     CML DO bi=myBxLo(myThid),myBxHi(myThid)
55     CML CALL GAD_DIFF_X(bi,bj,k,xA,diff1,localT,df,myThid)
56     CML DO j=1-Oly,sNy+Oly
57     CML DO i=1-Olx,sNx+Olx
58     CML fZon(i,j) = fZon(i,j) + df(i,j)
59     CML ENDDO
60     CML ENDDO
61     CML CALL GAD_DIFF_Y(bi,bj,k,yA,diff1,localT,df,myThid)
62     CML DO j=1-Oly,sNy+Oly
63     CML DO i=1-Olx,sNx+Olx
64     CML fMer(i,j) = fMer(i,j) + df(i,j)
65     CML ENDDO
66     CML ENDDO
67     CMLC-- Divergence of fluxes: update scalar field
68     CML DO j=1-Oly,sNy+Oly-1
69     CML DO i=1-Olx,sNx+Olx-1
70     CML HEFF(i,j,1,bi,bj)=HEFF(i,j,1,bi,bj) + DELTT *
71     CML & maskC(i,j,kSurface,bi,bj)*recip_rA(i,j,bi,bj)
72     CML & *( (fZon(i+1,j)-fZon(i,j))
73     CML & +(fMer(i,j+1)-fMer(i,j))
74     CML & )
75     CML & )
76     CML ENDDO
77     CML ENDDO
78     CML ENDDO
79     CML ENDDO
80    
81 mlosch 1.1 C NOW DO DIFFUSION ON H(I,J,3)
82     C NOW CALCULATE DIFFUSION COEF ROUGHLY
83     DO bj=myByLo(myThid),myByHi(myThid)
84     DO bi=myBxLo(myThid),myBxHi(myThid)
85     DO j=1-OLy,sNy+OLy
86     DO i=1-OLx,sNx+OLx
87     DIFFA(I,J,bi,bj)=
88     & DIFF1*MIN( _dxF(I,J,bi,bj), _dyF(I,J,bi,bj))
89     ENDDO
90     ENDDO
91     ENDDO
92     ENDDO
93     CALL DIFFUS(HEFF,DIFFA,HEFFM,DELTT, myThid)
94    
95     DO bj=myByLo(myThid),myByHi(myThid)
96     DO bi=myBxLo(myThid),myBxHi(myThid)
97     DO j=1-OLy,sNy+OLy
98     DO i=1-OLx,sNx+OLx
99     HEFF(I,J,1,bi,bj)=(HEFF(I,J,1,bi,bj)+HEFF(I,J,3,bi,bj))
100     & *HEFFM(I,J,bi,bj)
101     ENDDO
102     ENDDO
103     ENDDO
104     ENDDO
105    
106     C NOW CALCULATE DIFFUSION COEF ROUGHLY
107     DO bj=myByLo(myThid),myByHi(myThid)
108     DO bi=myBxLo(myThid),myBxHi(myThid)
109     DO j=1-OLy,sNy+OLy
110     DO i=1-OLx,sNx+OLx
111     DIFFA(I,J,bi,bj)=
112     & -(MIN( _dxF(I,J,bi,bj), _dyF(I,J,bi,bj)))**2/DELTT
113     ENDDO
114     ENDDO
115     ENDDO
116     ENDDO
117     CALL DIFFUS(HEFF,DIFFA,HEFFM,DELTT, myThid)
118    
119     DO bj=myByLo(myThid),myByHi(myThid)
120     DO bi=myBxLo(myThid),myBxHi(myThid)
121     DO j=1-OLy,sNy+OLy
122     DO i=1-OLx,sNx+OLx
123     HEFF(I,J,1,bi,bj)=(HEFF(I,J,1,bi,bj)+HEFF(I,J,3,bi,bj))
124     & *HEFFM(I,J,bi,bj)
125     ENDDO
126     ENDDO
127     ENDDO
128     ENDDO
129    
130     RETURN
131     END

  ViewVC Help
Powered by ViewVC 1.1.22