/[MITgcm]/MITgcm_contrib/dgoldberg/CPL1/code/shelfice_restore_sealevel.F
ViewVC logotype

Contents of /MITgcm_contrib/dgoldberg/CPL1/code/shelfice_restore_sealevel.F

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


Revision 1.1 - (show annotations) (download)
Wed Jul 6 18:01:26 2016 UTC (9 years ago) by dgoldberg
Branch: MAIN
CVS Tags: HEAD
moving experiment out of shelfice_remeshing to replace with vertical remeshing only

1 C $Header: /u/gcmpack/MITgcm_contrib/verification_other/shelfice_remeshing/code/shelfice_restore_sealevel.F,v 1.4 2016/05/05 18:16:04 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 #ifndef ALLOW_SHELFICE
53 C !LOCAL VARIABLES:
54 C == Local variables ==
55 C i,j :: Loop counters
56 INTEGER i, j, jsl
57 _RL etarelax, lambda_obcs_t
58 CEOP
59
60 c DO bj=myByLo(myThid),myByHi(myThid)
61 c DO bi=myBxLo(myThid),myBxHi(myThid)
62
63 C-- Zero out surface forcing terms below ice-shelf
64
65
66 IF (shelfice_etarestore_spongewidth.eq.0) then
67 shelfice_etarestore_spongewidth = spongeThickness
68 ENDIF
69
70 IF (shelficeetarelax.eq.0.0) then
71 shelficeetaRelax = Vrelaxobcsbound
72 ENDIF
73
74
75 #ifdef ALLOW_OBCS_NORTH
76 IF ( OBCSsponge_N .AND. shelficeEtaSponge ) THEN
77 DO i=1,sNx
78 IF ( OB_Jn(i,bi,bj).NE.OB_indexNone ) THEN
79 DO jsl= 1,shelfice_etarestore_spongewidth-1
80 j=OB_Jn(i,bi,bj)-jsl
81 IF ((j.ge.jmin).and.(j.le.jmax)) THEN
82 IF (.true.) THEN
83 etarelax = OBNeta(i,bi,bj)
84 ELSE
85 etarelax=(
86 & float(shelfice_etarestore_spongewidth-jsl)*OBNeta(i,bi,bj)
87 & + float(jsl)*etan(i,j,bi,bj) )
88 & / float(shelfice_etarestore_spongewidth)
89 ENDIF
90 lambda_obcs_t = (
91 & float(jsl)*shelficeEtaRelax
92 & + float(jsl)*Vrelaxobcsinner)
93 & / float(shelfice_etarestore_spongewidth)
94 IF (lambda_obcs_t.ne.0.) THEN
95 lambda_obcs_t = 1. _d 0 / lambda_obcs_t
96 ELSE
97 lambda_obcs_t = 0. _d 0
98 ENDIF
99 EmPmR(i,j,bi,bj) =
100 & maskInC(i,j,bi,bj) * lambda_obcs_t
101 & * ( etan(i,j,bi,bj) - etarelax ) * rhoConst
102 ENDIF
103 ENDDO
104 ENDIF
105 ENDDO
106 ENDIF
107 #endif
108
109
110
111
112
113
114 c ENDDO
115 c ENDDO
116
117 #endif
118 #endif /* ALLOW_SHELFICE */
119 RETURN
120 END

  ViewVC Help
Powered by ViewVC 1.1.22