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

Diff of /MITgcm_contrib/dgoldberg/streamice/streamice_init_varia.F

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

revision 1.3 by dgoldberg, Tue Sep 4 21:11:44 2012 UTC revision 1.4 by dgoldberg, Tue Sep 18 17:06:48 2012 UTC
# Line 18  C     \================================= Line 18  C     \=================================
18  C     === Global variables ===  C     === Global variables ===
19  #include "SIZE.h"  #include "SIZE.h"
20  #include "GRID.h"  #include "GRID.h"
21    #include "SET_GRID.h"
22  #include "EEPARAMS.h"  #include "EEPARAMS.h"
23  #include "PARAMS.h"  #include "PARAMS.h"
24  #include "STREAMICE.h"  #include "STREAMICE.h"
# Line 34  C     === Local variables === Line 35  C     === Local variables ===
35  C     I,J,bi,bj - Loop counters  C     I,J,bi,bj - Loop counters
36        INTEGER i, j, k, bi, bj, Gi, Gj        INTEGER i, j, k, bi, bj, Gi, Gj
37        INTEGER col_y, col_x        INTEGER col_y, col_x
38        _RL slope_pos, c1        _RL slope_pos, c1, x, y, lenx, leny
39        CHARACTER*(MAX_LEN_MBUF) msgBuf        CHARACTER*(MAX_LEN_MBUF) msgBuf
40  CEOP  CEOP
41    
# Line 55  C     ZERO OUT FLOATING POINT ARRAYS Line 56  C     ZERO OUT FLOATING POINT ARRAYS
56            area_shelf_streamice(i,j,bi,bj) = 0. _d 0            area_shelf_streamice(i,j,bi,bj) = 0. _d 0
57            mass_ice_streamice(i,j,bi,bj) = 0. _d 0            mass_ice_streamice(i,j,bi,bj) = 0. _d 0
58            BDOT_streamice(i,j,bi,bj) = 0. _d 0            BDOT_streamice(i,j,bi,bj) = 0. _d 0
59            C_basal_friction(i,j,bi,bj) = C_basal_fric_const  !           C_basal_friction(i,j,bi,bj) = C_basal_fric_const
60            A_glen(i,j,bi,bj) = A_glen_isothermal            A_glen(i,j,bi,bj) = A_glen_isothermal
61  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
62            ru_old_si(i,j,bi,bj) = 0. _d 0            ru_old_si(i,j,bi,bj) = 0. _d 0
# Line 64  C     ZERO OUT FLOATING POINT ARRAYS Line 65  C     ZERO OUT FLOATING POINT ARRAYS
65            zv_old_si(i,j,bi,bj) = 0. _d 0            zv_old_si(i,j,bi,bj) = 0. _d 0
66            h_after_uflux_SI(i,j,bi,bj) = 0. _d 0            h_after_uflux_SI(i,j,bi,bj) = 0. _d 0
67  #endif  #endif
68    #ifdef STREAMICE_HYBRID_STRESS
69              do k=1,Nr
70               visc_streamice_full(i,j,k,bi,bj) =
71         &     eps_glen_min**((1-n_glen)/n_glen)
72              enddo      
73    #endif
74           ENDDO           ENDDO
75          ENDDO          ENDDO
76         ENDDO         ENDDO
# Line 105  C     INIT. INTEGER ARRAYS Line 112  C     INIT. INTEGER ARRAYS
112         ENDDO         ENDDO
113        ENDDO        ENDDO
114    
115  !ph      SELECT CASE (TRIM(STREAMICEthickInit))  ! initialize thickness
116            
117        IF ( STREAMICEthickInit.EQ.'PARAM' ) THEN        IF ( STREAMICEthickInit.EQ.'PARAM' ) THEN
118    
# Line 167  C             IF (flow_dir .EQ. 2.0) THE Line 174  C             IF (flow_dir .EQ. 2.0) THE
174          ENDDO          ENDDO
175         ENDDO         ENDDO
176    
   
   
177        ELSE IF ( STREAMICEthickInit.EQ.'FILE' ) THEN        ELSE IF ( STREAMICEthickInit.EQ.'FILE' ) THEN
178    
179         IF ( STREAMICEthickFile .NE. ' ' ) THEN         IF ( STREAMICEthickFile .NE. ' ' ) THEN
# Line 182  C The 0 is the "iteration" argument. The Line 187  C The 0 is the "iteration" argument. The
187             DO i=1,sNx             DO i=1,sNx
188              Gi = (myXGlobalLo-1)+(bi-1)*sNx+i              Gi = (myXGlobalLo-1)+(bi-1)*sNx+i
189              Gj = (myYGlobalLo-1)+(bj-1)*sNy+j              Gj = (myYGlobalLo-1)+(bj-1)*sNy+j
190              IF ((Gi.lt.Nx).and.(Gj.lt.Ny)) THEN              IF ((Gi.lt.Nx.OR.STREAMICE_EW_periodic).and.
191         &          (Gj.lt.Ny.OR.STREAMICE_NS_periodic)) THEN
192               IF (H_streamice(i,j,bi,bj).GT.0. _d 0) THEN               IF (H_streamice(i,j,bi,bj).GT.0. _d 0) THEN
193                area_shelf_streamice(i,j,bi,bj) = rA(i,j,bi,bj)                area_shelf_streamice(i,j,bi,bj) = rA(i,j,bi,bj)
194                STREAMICE_hmask(i,j,bi,bj) = 1.0                STREAMICE_hmask(i,j,bi,bj) = 1.0
# Line 208  C The 0 is the "iteration" argument. The Line 214  C The 0 is the "iteration" argument. The
214       &                    SQUEEZE_RIGHT , 1)       &                    SQUEEZE_RIGHT , 1)
215        ENDIF        ENDIF
216    
217        CALL STREAMICE_UPD_FFRAC_UNCOUPLED ( myThid )      ! finish initialize thickness
218    
219    ! initialize basal traction
220    
221          IF ( STREAMICEbasalTracConfig.EQ.'FILE' ) THEN
222    
223           IF ( STREAMICEbasalTracFile .NE. ' ' ) THEN
224            _BARRIER
225    C The 0 is the "iteration" argument. The ' ' is an empty suffix
226            CALL READ_FLD_XY_RS( STREAMICEbasalTracFile, ' ',
227         &      C_basal_friction, 0, myThid )
228    
229           ELSE
230            WRITE(msgBuf,'(A)') 'INIT THICKNESS - FILENAME MISSING'
231            CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
232         &                    SQUEEZE_RIGHT , 1)
233           ENDIF
234          
235          ELSE IF (STREAMICEbasalTracConfig.EQ.'UNIFORM' ) THEN
236    
237            DO bj = myByLo(myThid), myByHi(myThid)
238             DO bi = myBxLo(myThid), myBxHi(myThid)
239              DO j=1,sNy
240               DO i=1,sNx
241                C_basal_friction(i,j,bi,bj) = C_basal_fric_const
242               ENDDO
243              ENDDO
244             ENDDO
245            ENDDO
246    
247          ELSE IF (STREAMICEbasalTracConfig.EQ.'2DPERIODIC' ) THEN
248                
249           lenx = sNx*nSx*nPx*delX(1)
250           leny = sNy*nSy*nPy*delY(1)
251           print *, 'lenx', lenx
252           print *, 'leny', leny
253           DO bj = myByLo(myThid), myByHi(myThid)
254            DO bi = myBxLo(myThid), myBxHi(myThid)
255             DO j=1,sNy
256              DO i=1,sNx
257               x = xC(i,j,bi,bj)
258               y = yC(i,j,bi,bj)
259               C_basal_friction(i,j,bi,bj) =
260         &      sqrt(C_basal_fric_const**2*
261         &        (1+sin(2*streamice_kx_b_init*PI*x/lenx)*
262         &           sin(2*streamice_ky_b_init*PI*y/leny)))
263              ENDDO
264             ENDDO
265            ENDDO
266           ENDDO
267    
268          ELSE IF (STREAMICEbasalTracConfig.EQ.'1DPERIODIC' ) THEN
269                
270           lenx = sNx*nSx*nPx*delX(1)
271           print *, 'lenx', lenx
272           DO bj = myByLo(myThid), myByHi(myThid)
273            DO bi = myBxLo(myThid), myBxHi(myThid)
274             DO j=1,sNy
275              DO i=1,sNx
276               x = xC(i,j,bi,bj)
277               y = yC(i,j,bi,bj)
278               C_basal_friction(i,j,bi,bj) =
279         &      sqrt(C_basal_fric_const**2*(1+
280         &        sin(2*streamice_kx_b_init*PI*x/lenx)))
281              ENDDO
282             ENDDO
283            ENDDO
284           ENDDO
285    
286          ELSE
287    
288           WRITE(msgBuf,'(A)') 'INIT THICKNESS - NOT IMPLENTED'
289           CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
290         &                    SQUEEZE_RIGHT , 1)
291          ENDIF
292    
293    ! finish initialize basal traction
294    
295          CALL STREAMICE_UPD_FFRAC_UNCOUPLED ( myThid )
296    
297        _EXCH_XY_RL(H_streamice, myThid )        _EXCH_XY_RL(H_streamice, myThid )
298        _EXCH_XY_RL(STREAMICE_hmask, myThid )        _EXCH_XY_RL(STREAMICE_hmask, myThid )
299        _EXCH_XY_RL(area_shelf_streamice, myThid )        _EXCH_XY_RL(area_shelf_streamice, myThid )
300          _EXCH_XY_RL(C_basal_friction, myThid )
301    
302    
303    #ifdef STREAMICE_HYBRID_STRESS
304    
305          CALL STREAMICE_VISC_BETA (myThid)
306    
307    #endif
308    
309        CALL WRITE_FLD_XY_RL ( "H_streamice", "init",        CALL WRITE_FLD_XY_RL ( "H_streamice", "init",
310       & H_streamIce, 0, myThid )       & H_streamIce, 0, myThid )
# Line 226  C The 0 is the "iteration" argument. The Line 318  C The 0 is the "iteration" argument. The
318  !       CALL STREAMICE_VEL_SOLVE( myThid )  !       CALL STREAMICE_VEL_SOLVE( myThid )
319    
320        CALL WRITE_FLD_XY_RL ( "U_init", "",        CALL WRITE_FLD_XY_RL ( "U_init", "",
321       &   U_streamice, 0, myThid )       &   C_basal_friction, 0, myThid )
322        CALL WRITE_FLD_XY_RL ( "V_init", "",        CALL WRITE_FLD_XY_RL ( "V_init", "",
323       &   V_streamice, 0, myThid )       &   V_streamice, 0, myThid )
324    

Legend:
Removed from v.1.3  
changed lines
  Added in v.1.4

  ViewVC Help
Powered by ViewVC 1.1.22