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

Annotation of /MITgcm/pkg/thsice/thsice_main.F

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


Revision 1.2 - (hide annotations) (download)
Wed Apr 7 23:40:34 2004 UTC (20 years, 1 month ago) by jmc
Branch: MAIN
CVS Tags: checkpoint52n_post, checkpoint53d_post, checkpoint54a_pre, checkpoint54a_post, checkpoint53c_post, checkpoint53b_post, checkpoint53b_pre, checkpoint52m_post, checkpoint53a_post, checkpoint54, checkpoint53, checkpoint53g_post, checkpoint53f_post, checkpoint53d_pre
Changes since 1.1: +49 -5 lines
major changes in pkg/thsice: allows atmospheric model (AIM) to use thsice.
- split thsice_therm.F in 2 S/R: thsice_solve4temp.F & thsice_calc_thickn.F
- move most of the ocean & bulk_force interface in thsice_main.F
- add a "slab ocean" component to be used with atmospheric model

1 jmc 1.2 C $Header: /u/gcmpack/MITgcm/pkg/thsice/thsice_main.F,v 1.1 2003/11/23 01:20:13 jmc Exp $
2 jmc 1.1 C $Name: $
3    
4     #include "THSICE_OPTIONS.h"
5    
6 jmc 1.2 CBOP
7 jmc 1.1 C !ROUTINE: THSICE_MAIN
8     C !INTERFACE:
9     SUBROUTINE THSICE_MAIN(
10     I myTime, myIter, myThid )
11 jmc 1.2 C !DESCRIPTION: \bv
12 jmc 1.1 C *==========================================================*
13 jmc 1.2 C | S/R THSICE_MAIN
14 jmc 1.1 C | o Therm_SeaIce main routine.
15     C | step forward Thermodynamic_SeaIce variables and modify
16     C | ocean surface forcing accordingly.
17     C *==========================================================*
18    
19     C !USES:
20     IMPLICIT NONE
21 jmc 1.2
22 jmc 1.1 C === Global variables ===
23     #include "SIZE.h"
24     #include "EEPARAMS.h"
25     #include "PARAMS.h"
26 jmc 1.2 #include "GRID.h"
27     #include "DYNVARS.h"
28 jmc 1.1 #include "FFIELDS.h"
29     #include "THSICE_PARAMS.h"
30 jmc 1.2 #include "THSICE_VARS.h"
31     #ifdef ALLOW_BULK_FORCE
32     #include "BULKF.h"
33     #endif
34 jmc 1.1
35     C !INPUT/OUTPUT PARAMETERS:
36     C === Routine arguments ===
37     C myIter :: iteration counter for this thread
38     C myTime :: time counter for this thread
39     C myThid :: thread number for this instance of the routine.
40     _RL myTime
41     INTEGER myIter
42     INTEGER myThid
43 jmc 1.2 CEOP
44 jmc 1.1
45     #ifdef ALLOW_THSICE
46     C !LOCAL VARIABLES:
47     C === Local variables ===
48     INTEGER i,j
49     INTEGER bi,bj
50     INTEGER iMin, iMax
51     INTEGER jMin, jMax
52 jmc 1.2 _RL prcAtm(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
53     _RL evpAtm(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
54     _RL flxSW (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
55 jmc 1.1
56     _RL tauFac
57    
58     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
59    
60     IF ( stressReduction.GT. 0. _d 0 ) THEN
61     iMin = 1-Olx
62     iMax = sNx+Olx-1
63     jMin = 1-Oly
64     jMax = sNy+Oly-1
65     ELSE
66     iMin = 1
67     iMax = sNx
68     jMin = 1
69     jMax = sNy
70     ENDIF
71    
72     DO bj=myByLo(myThid),myByHi(myThid)
73     DO bi=myBxLo(myThid),myBxHi(myThid)
74 jmc 1.2
75     DO j = jMin, jMax
76     DO i = iMin, iMax
77     hOceMxL(i,j,bi,bj) = hfacC(i,j,1,bi,bj)*drF(1)
78     tOceMxL(i,j,bi,bj) = theta(i,j,1,bi,bj)
79     sOceMxL(i,j,bi,bj) = salt (i,j,1,bi,bj)
80     v2ocMxL(i,j,bi,bj) =
81     & ( uvel(i,j,1,bi,bj)*uvel(i,j,1,bi,bj)
82     & + uvel(i+1,j,1,bi,bj)*uvel(i+1,j,1,bi,bj)
83     & + vvel(i,j+1,1,bi,bj)*vvel(i,j+1,1,bi,bj)
84     & + vvel(i,j,1,bi,bj)*vvel(i,j,1,bi,bj)
85     & )*0.5 _d 0
86     prcAtm(i,j) = 0.
87     evpAtm(i,j) = 0.
88     flxSW (i,j) = 0.
89     snowPrc(i,j,bi,bj) = 0. _d 0
90     #ifdef ALLOW_BULK_FORCE
91     prcAtm(i,j) = ( rain(i,j,bi,bj)+runoff(i,j,bi,bj) )*rhofw
92     flxSW (i,j) = solar(i,j,bi,bj)
93     IF ( iceMask(i,j,bi,bj).GT.0. _d 0
94     & .AND. Tair(i,j,bi,bj).LE.Tf0kel ) THEN
95     snowPrc(i,j,bi,bj) = rain(i,j,bi,bj)*rhofw
96     ENDIF
97     #endif
98     ENDDO
99     ENDDO
100    
101 jmc 1.1 CALL THSICE_STEP_FWD(
102     I bi, bj, iMin, iMax, jMin, jMax,
103 jmc 1.2 I prcAtm,
104     U evpAtm, flxSW,
105 jmc 1.1 I myTime, myIter, myThid )
106 jmc 1.2
107     CALL THSICE_AVE(
108     I evpAtm, flxSW,
109     I bi,bj, myTime, myIter, myThid )
110    
111 jmc 1.1 c ENDDO
112     c ENDDO
113    
114     c IF ( .FALSE. ) THEN
115     IF ( stressReduction.GT. 0. _d 0 ) THEN
116     DO j = jMin, jMax
117     DO i = iMin+1,iMax
118     tauFac = stressReduction
119     & *(iceMask(i-1,j,bi,bj)+iceMask(i,j,bi,bj))*0.5 _d 0
120     fu(i,j,bi,bj) = (1. _d 0 - tauFac)*fu(i,j,bi,bj)
121     ENDDO
122     ENDDO
123     DO j = jMin+1, jMax
124     DO i = iMin, iMax
125     tauFac = stressReduction
126     & *(iceMask(i,j-1,bi,bj)+iceMask(i,j,bi,bj))*0.5 _d 0
127     fv(i,j,bi,bj) = (1. _d 0 - tauFac)*fv(i,j,bi,bj)
128     ENDDO
129     ENDDO
130     ENDIF
131    
132     C-- end bi,bj loop
133     ENDDO
134     ENDDO
135    
136     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
137     #endif /*ALLOW_THSICE*/
138    
139     RETURN
140     END

  ViewVC Help
Powered by ViewVC 1.1.22