/[MITgcm]/MITgcm/pkg/thsice/thsice_do_advect.F
ViewVC logotype

Contents of /MITgcm/pkg/thsice/thsice_do_advect.F

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


Revision 1.5 - (show annotations) (download)
Thu Apr 4 00:42:07 2013 UTC (11 years, 2 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint64y, checkpoint64x, checkpoint64z, checkpoint64q, checkpoint64p, checkpoint64s, checkpoint64r, checkpoint64u, checkpoint64t, checkpoint64w, checkpoint64v, checkpoint64i, checkpoint64h, checkpoint64k, checkpoint64j, checkpoint64m, checkpoint64l, checkpoint64o, checkpoint64n, checkpoint64g, checkpoint65, checkpoint65p, checkpoint65q, checkpoint65j, checkpoint65k, checkpoint65h, checkpoint65i, checkpoint65n, checkpoint65o, checkpoint65l, checkpoint65m, checkpoint65b, checkpoint65c, checkpoint65a, checkpoint65f, checkpoint65g, checkpoint65d, checkpoint65e
Changes since 1.4: +12 -8 lines
Forgot to move (after the advection) THSICE_AVE call in new sequence of calls

1 C $Header: /u/gcmpack/MITgcm/pkg/thsice/thsice_do_advect.F,v 1.4 2013/01/22 23:31:09 heimbach Exp $
2 C $Name: $
3
4 #include "THSICE_OPTIONS.h"
5
6 CBOP
7 C !ROUTINE: THSICE_DO_ADVECT
8 C !INTERFACE:
9 SUBROUTINE THSICE_DO_ADVECT(
10 I biArg, bjArg, myTime, myIter, myThid )
11
12 C !DESCRIPTION: \bv
13 C *==========================================================*
14 C | SUBROUTINE THSICE_DO_ADVECT
15 C | o wraper for pkg/thSIce advection-diffusion calls
16 C *==========================================================*
17 C \ev
18 C !USES:
19 IMPLICIT NONE
20
21 C === Global variables ===
22 #include "SIZE.h"
23 #include "EEPARAMS.h"
24 #include "PARAMS.h"
25 #include "FFIELDS.h"
26 #include "THSICE_SIZE.h"
27 #include "THSICE_PARAMS.h"
28 #include "THSICE_VARS.h"
29 #ifdef ALLOW_AUTODIFF_TAMC
30 # include "tamc.h"
31 #endif
32
33 C !INPUT/OUTPUT PARAMETERS:
34 C === Routine arguments ===
35 C biArg :: Tile 1rst index argument
36 C bjArg :: Tile 2nd index argument
37 C myTime :: Current time in simulation (s)
38 C myIter :: Current iteration number
39 C myThid :: My Thread Id. number
40 INTEGER biArg, bjArg
41 _RL myTime
42 INTEGER myIter
43 INTEGER myThid
44 CEOP
45
46 C !LOCAL VARIABLES:
47 C === Local variables ===
48 C bi, bj :: Tile indices
49 C uIce/vIce :: ice velocity on C-grid [m/s]
50 INTEGER bi, bj
51 #ifndef OLD_THSICE_CALL_SEQUENCE
52 INTEGER i, j
53 INTEGER iMin, iMax, jMin, jMax
54 #endif
55 _RL uIce(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
56 _RL vIce(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
57
58 IF ( thSIceAdvScheme.GT.0 .AND. biArg.EQ.0 .AND. bjArg.EQ.0 ) THEN
59 #ifndef OLD_THSICE_CALL_SEQUENCE
60 c iMin = 1
61 c iMax = sNx
62 c jMin = 1
63 c jMax = sNy
64 iMin = 1-OLx
65 iMax = sNx+OLx-1
66 jMin = 1-OLy
67 jMax = sNy+OLy-1
68 DO bj = myByLo(myThid), myByHi(myThid)
69 DO bi = myBxLo(myThid), myBxHi(myThid)
70 #ifdef ALLOW_AUTODIFF_TAMC
71 act1 = bi - myBxLo(myThid)
72 max1 = myBxHi(myThid) - myBxLo(myThid) + 1
73 act2 = bj - myByLo(myThid)
74 max2 = myByHi(myThid) - myByLo(myThid) + 1
75 act3 = myThid - 1
76 max3 = nTx*nTy
77 act4 = ikey_dynamics - 1
78 ticekey = (act1 + 1) + act2*max1
79 & + act3*max1*max2
80 & + act4*max1*max2*max3
81 #endif /* ALLOW_AUTODIFF_TAMC */
82
83 CALL THSICE_GET_VELOCITY(
84 O uIce, vIce,
85 I bi,bj, myTime, myIter, myThid )
86 #ifdef ALLOW_AUTODIFF_TAMC
87 CADJ STORE icemask(:,:,bi,bj) =
88 CADJ & comlev1_bibj, key=ticekey, byte=isbyte
89 CADJ STORE qice1(:,:,bi,bj) =
90 CADJ & comlev1_bibj, key=ticekey, byte=isbyte
91 CADJ STORE hOceMxL(:,:,bi,bj) =
92 CADJ & comlev1_bibj, key=ticekey, byte=isbyte
93 #endif
94 CALL THSICE_ADVDIFF(
95 U uIce, vIce,
96 I bi,bj, myTime, myIter, myThid )
97 #ifdef ALLOW_AUTODIFF_TAMC
98 CADJ STORE hOceMxL(:,:,bi,bj) =
99 CADJ & comlev1_bibj, key=ticekey, byte=isbyte
100 CADJ STORE snowHeight(:,:,bi,bj) =
101 CADJ & comlev1_bibj, key=ticekey, byte=isbyte
102 CADJ STORE iceHeight(:,:,bi,bj) =
103 CADJ & comlev1_bibj, key=ticekey, byte=isbyte
104 CADJ STORE iceMask(:,:,bi,bj) =
105 CADJ & comlev1_bibj, key=ticekey, byte=isbyte
106 #endif
107 DO j = jMin, jMax
108 DO i = iMin, iMax
109 IF ( hOceMxL(i,j,bi,bj).GT.0. _d 0 ) THEN
110 Qnet(i,j,bi,bj) = Qnet(i,j,bi,bj) - oceQnet(i,j,bi,bj)
111 EmPmR(i,j,bi,bj)= EmPmR(i,j,bi,bj)- oceFWfx(i,j,bi,bj)
112 saltFlux(i,j,bi,bj)=saltFlux(i,j,bi,bj) - oceSflx(i,j,bi,bj)
113 ENDIF
114 C-- Compute Sea-Ice Loading (= mass of sea-ice + snow / area unit)
115 sIceLoad(i,j,bi,bj) = ( snowHeight(i,j,bi,bj)*rhos
116 & + iceHeight(i,j,bi,bj)*rhoi
117 & )*iceMask(i,j,bi,bj)
118 ENDDO
119 ENDDO
120
121 C-- cumulate time-averaged fields and also fill-up flux diagnostics
122 CALL THSICE_AVE(
123 I bi,bj, myTime, myIter, myThid )
124
125 ENDDO
126 ENDDO
127
128 IF ( stressReduction.GT. 0. _d 0 )
129 & _EXCH_XY_RL( iceMask, myThid )
130 #ifdef ATMOSPHERIC_LOADING
131 IF ( useRealFreshWaterFlux )
132 & _EXCH_XY_RS( sIceLoad, myThid )
133 #endif
134 #endif /* ndef OLD_THSICE_CALL_SEQUENCE */
135
136 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
137
138 #ifdef OLD_THSICE_CALL_SEQUENCE
139 ELSEIF ( thSIceAdvScheme.GT.0 ) THEN
140 bi = biArg
141 bj = bjArg
142 CALL THSICE_GET_VELOCITY(
143 O uIce, vIce,
144 I bi,bj, myTime, myIter, myThid )
145 CALL THSICE_ADVDIFF(
146 U uIce, vIce,
147 I bi,bj, myTime, myIter, myThid )
148 #endif /* OLD_THSICE_CALL_SEQUENCE */
149 ENDIF
150
151 RETURN
152 END

  ViewVC Help
Powered by ViewVC 1.1.22