/[MITgcm]/MITgcm_contrib/dgoldberg/streamice/streamice_advect_thickness.F
ViewVC logotype

Annotation of /MITgcm_contrib/dgoldberg/streamice/streamice_advect_thickness.F

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


Revision 1.2 - (hide annotations) (download)
Wed May 2 02:36:01 2012 UTC (13 years, 2 months ago) by heimbach
Branch: MAIN
Changes since 1.1: +18 -282 lines
Various updates to streamice code

1 heimbach 1.1 C $Header: /u/gcmpack/MITgcm/pkg/streamice/streamice_init_varia.F,v 1.6 2011/06/29 16:24:10 dng Exp $
2     C $Name: $
3    
4     #include "STREAMICE_OPTIONS.h"
5    
6     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
7    
8    
9     CBOP
10     SUBROUTINE STREAMICE_ADVECT_THICKNESS ( myThid, time_step )
11    
12     C /============================================================\
13     C | SUBROUTINE |
14     C | o |
15     C |============================================================|
16     C | |
17     C \============================================================/
18     IMPLICIT NONE
19    
20     C === Global variables ===
21     #include "SIZE.h"
22     #include "GRID.h"
23     #include "EEPARAMS.h"
24     #include "PARAMS.h"
25     #include "STREAMICE.h"
26     #include "STREAMICE_ADV.h"
27 heimbach 1.2 #ifdef ALLOW_AUTODIFF_TAMC
28     # include "tamc.h"
29     #endif
30 heimbach 1.1
31     INTEGER myThid
32     _RL time_step
33    
34     #ifdef ALLOW_STREAMICE
35    
36     INTEGER i, j, bi, bj
37     _RL thick_bd
38     _RL SLOPE_LIMITER
39     _RL sec_per_year, time_step_loc
40     external SLOPE_LIMITER
41    
42     sec_per_year = 365.*86400.
43    
44     time_step_loc = time_step / sec_per_year
45    
46 heimbach 1.2 #ifdef ALLOW_AUTODIFF_TAMC
47     CADJ STORE streamice_hmask = comlev1, key=ikey_dynamics
48     #endif
49    
50 heimbach 1.1 DO bj=myByLo(myThid),myByHi(myThid)
51     DO bi=myBxLo(myThid),myBxHi(myThid)
52     DO j=1-OLy,sNy+OLy
53     DO i=1-OLx,sNx+OLx
54     hflux_x_SI (i,j,bi,bj) = 0. _d 0
55     hflux_y_SI (i,j,bi,bj) = 0. _d 0
56     hflux_x_SI2 (i,j,bi,bj) = 0. _d 0
57     hflux_y_SI2 (i,j,bi,bj) = 0. _d 0
58     IF (STREAMICE_hmask(i,j,bi,bj).eq.1.0) THEN
59     h_after_uflux_SI (i,j,bi,bj) =
60     & H_streamice (i,j,bi,bj)
61     ENDIF
62    
63     thick_bd = h_bdry_values_SI (i,j,bi,bj)
64     IF (thick_bd .ne. 0. _d 0) THEN
65     h_after_uflux_SI (i,j,bi,bj) = thick_bd
66     ENDIF
67     ENDDO
68     ENDDO
69     ENDDO
70     ENDDO
71    
72     ! PRINT *, "H in last row ", H_streamice(81,20,1,1)
73    
74 heimbach 1.2 #ifdef ALLOW_AUTODIFF_TAMC
75     CADJ STORE h_after_uflux_si = comlev1, key=ikey_dynamics
76     CADJ STORE streamice_hmask = comlev1, key=ikey_dynamics
77     #endif
78    
79 heimbach 1.1 CALL STREAMICE_ADVECT_THICKNESS_X ( myThid,
80     O hflux_x_SI,
81     O h_after_uflux_SI,
82     I time_step_loc )
83    
84     ! PRINT *, "H in last row ", H_streamice(81,20,1,1)
85    
86     DO bj=myByLo(myThid),myByHi(myThid)
87     DO bi=myBxLo(myThid),myBxHi(myThid)
88     DO j=1-OLy,sNy+OLy
89     DO i=1-OLx,sNx+OLx
90     h_after_vflux_SI (i,j,bi,bj) =
91     & h_after_uflux_SI (i,j,bi,bj)
92     ENDDO
93     ENDDO
94     ENDDO
95     ENDDO
96    
97 heimbach 1.2 #ifdef ALLOW_AUTODIFF_TAMC
98     CADJ STORE h_after_vflux_si = comlev1, key=ikey_dynamics
99     CADJ STORE streamice_hmask = comlev1, key=ikey_dynamics
100     #endif
101    
102 heimbach 1.1 CALL STREAMICE_ADVECT_THICKNESS_Y ( myThid,
103     O hflux_y_SI,
104     O h_after_vflux_SI,
105     I time_step_loc )
106    
107     ! PRINT *, "H in last row ", H_streamice(81,20,1,1)
108    
109     DO bj=myByLo(myThid),myByHi(myThid)
110     DO bi=myBxLo(myThid),myBxHi(myThid)
111     DO j=1-OLy,sNy+OLy
112     DO i=1-OLx,sNx+OLx
113     IF (STREAMICE_hmask(i,j,bi,bj).eq.1.0) THEN
114     H_streamice (i,j,bi,bj) =
115     & h_after_vflux_SI (i,j,bi,bj)
116     ENDIF
117     ENDDO
118     ENDDO
119     ENDDO
120     ENDDO
121    
122     ! PRINT *, "H in last row ", H_streamice(81,20,1,1)
123    
124     CALL STREAMICE_ADV_FRONT ( myThid, time_step_loc )
125    
126     ! PRINT *, "H in last row ", H_streamice(81,20,1,1)
127    
128     _EXCH_XY_RL( H_streamice, myThid )
129     _EXCH_XY_RL( area_shelf_streamice, myThid )
130     _EXCH_XY_RL( STREAMICE_hmask, myThid )
131    
132     PRINT *, "END STREAMICE_ADVECT_THICKNESS"
133    
134     #endif
135 heimbach 1.2 END
136 heimbach 1.1

  ViewVC Help
Powered by ViewVC 1.1.22