/[MITgcm]/MITgcm_contrib/shelfice_remeshing/DIG/code/shelfice_restore_sealevel.F
ViewVC logotype

Annotation of /MITgcm_contrib/shelfice_remeshing/DIG/code/shelfice_restore_sealevel.F

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


Revision 1.1 - (hide annotations) (download)
Fri Apr 1 10:19:38 2016 UTC (9 years, 3 months ago) by dgoldberg
Branch: MAIN
CVS Tags: HEAD
Added rough code to dig ice shelf to make continuous ocean

1 dgoldberg 1.1 C $Header: /u/gcmpack/MITgcm_contrib/verification_other/shelfice_remeshing/code/shelfice_restore_sealevel.F,v 1.3 2016/01/31 23:08:17 dgoldberg Exp $
2     C $Name: $
3    
4     #include "SHELFICE_OPTIONS.h"
5     #include "OBCS_OPTIONS.h"
6    
7     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
8     CBOP
9     C !ROUTINE: SHELFICE_FORCING_SURF
10     C !INTERFACE:
11     SUBROUTINE SHELFICE_RESTORE_SEALEVEL(
12     I bi, bj, iMin, iMax, jMin, jMax,
13     I myTime, myIter, myThid )
14     C !DESCRIPTION: \bv
15     C *==========================================================*
16     C | S/R SHELFICE_FORCING_SURF
17     C | o Contains problem specific surface forcing
18     C *==========================================================*
19     C \ev
20    
21     C !USES:
22     IMPLICIT NONE
23     C == Global data ==
24     #include "SIZE.h"
25     #include "EEPARAMS.h"
26     #include "PARAMS.h"
27     #include "GRID.h"
28     #include "DYNVARS.h"
29     #include "SURFACE.h"
30     #include "FFIELDS.h"
31     #include "SHELFICE.h"
32     #include "OBCS_PARAMS.h"
33     #include "OBCS_GRID.h"
34     #include "OBCS_FIELDS.h"
35    
36    
37     C !INPUT/OUTPUT PARAMETERS:
38     C == Routine arguments ==
39     C bi,bj :: Current tile indices
40     C iMin,iMax :: Working range of x-index for applying forcing.
41     C jMin,jMax :: Working range of y-index for applying forcing.
42     C myTime :: Current time in simulation
43     C myIter :: Current iteration number in simulation
44     C myThid :: Thread Id number
45     INTEGER bi, bj
46     INTEGER iMin, iMax, jMin, jMax
47     _RL myTime
48     INTEGER myIter
49     INTEGER myThid
50    
51     #ifdef ALLOW_SHELFICE
52     C !LOCAL VARIABLES:
53     C == Local variables ==
54     C i,j :: Loop counters
55     INTEGER i, j, jsl
56     _RL etarelax, lambda_obcs_t
57     CEOP
58    
59     c DO bj=myByLo(myThid),myByHi(myThid)
60     c DO bi=myBxLo(myThid),myBxHi(myThid)
61    
62     C-- Zero out surface forcing terms below ice-shelf
63    
64    
65     IF (shelfice_etarestore_spongewidth.eq.0) then
66     shelfice_etarestore_spongewidth = spongeThickness
67     ENDIF
68    
69     IF (shelficeetarelax.eq.0.0) then
70     shelficeetaRelax = Vrelaxobcsbound
71     ENDIF
72    
73    
74     #ifdef ALLOW_OBCS_NORTH
75     IF ( OBCSsponge_N .AND. shelficeEtaSponge ) THEN
76     DO i=iMin,iMax
77     IF ( OB_Jn(i,bi,bj).NE.OB_indexNone ) THEN
78     DO jsl= 1,shelfice_etarestore_spongewidth-1
79     j=OB_Jn(i,bi,bj)-jsl
80     IF ((j.ge.jmin).and.(j.le.jmax)) THEN
81     IF (.true.) THEN
82     etarelax = OBNeta(i,bi,bj)
83     ELSE
84     etarelax=(
85     & float(shelfice_etarestore_spongewidth-jsl)*OBNeta(i,bi,bj)
86     & + float(jsl)*etah(i,j,bi,bj) )
87     & / float(shelfice_etarestore_spongewidth)
88     ENDIF
89     lambda_obcs_t = (
90     & float(jsl)*shelficeEtaRelax
91     & + float(jsl)*Vrelaxobcsinner)
92     & / float(shelfice_etarestore_spongewidth)
93     IF (lambda_obcs_t.ne.0.) THEN
94     lambda_obcs_t = 1. _d 0 / lambda_obcs_t
95     ELSE
96     lambda_obcs_t = 0. _d 0
97     ENDIF
98     EmPmR(i,j,bi,bj) =
99     & maskInC(i,j,bi,bj) * lambda_obcs_t
100     & * ( etah(i,j,bi,bj) - etarelax ) * rhoConst
101     ENDIF
102     ENDDO
103     ENDIF
104     ENDDO
105     ENDIF
106     #endif
107    
108    
109    
110    
111    
112    
113     c ENDDO
114     c ENDDO
115    
116     #endif /* ALLOW_SHELFICE */
117     RETURN
118     END

  ViewVC Help
Powered by ViewVC 1.1.22