/[MITgcm]/MITgcm_contrib/snarayan/streamice_oad_files/streamice_vel_solve_openad.F
ViewVC logotype

Annotation of /MITgcm_contrib/snarayan/streamice_oad_files/streamice_vel_solve_openad.F

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


Revision 1.1 - (hide annotations) (download)
Sun Nov 30 08:02:45 2014 UTC (10 years, 8 months ago) by snarayan
Branch: MAIN
Possible solution to sidestep strictAnonymous in the template

1 snarayan 1.1 C $Header: /u/gcmpack/MITgcm_contrib/dgoldberg/streamice_oad_files/streamice_vel_solve_openad.F,v 1.2 2014/11/25 18:29:18 dgoldberg Exp $
2     C $Name: $
3    
4     #include "STREAMICE_OPTIONS.h"
5     #ifdef ALLOW_AUTODIFF
6     # include "AUTODIFF_OPTIONS.h"
7     #endif
8    
9     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
10    
11     CBOP
12     SUBROUTINE STREAMICE_VEL_SOLVE_OPENAD ( myThid, maxNLIter,
13     & maxCGiter, myiter )
14     C /============================================================\
15     C | SUBROUTINE |
16     C | o |
17     C |============================================================|
18     C | |
19     C \============================================================/
20     IMPLICIT NONE
21    
22     C === Global variables ===
23     #include "SIZE.h"
24     #include "EEPARAMS.h"
25     #include "PARAMS.h"
26     #include "STREAMICE.h"
27     #include "STREAMICE_CG.h"
28    
29    
30     #ifdef ALLOW_AUTODIFF_TAMC
31     # include "tamc.h"
32     #endif
33    
34     C !INPUT/OUTPUT ARGUMENTS
35     INTEGER myThid
36     INTEGER maxNLIter
37     INTEGER maxCGIter
38     INTEGER myIter
39    
40     #ifdef ALLOW_STREAMICE
41    
42     C LOCAL VARIABLES
43    
44     INTEGER i, j, k, l, bi, bj, loopiter
45     CHARACTER*(MAX_LEN_MBUF) msgBuf
46    
47     INTEGER NL_iter
48     _RL err_last_change, cgtol
49     LOGICAL CONVERGED
50    
51     #ifdef ALLOW_OPENAD
52     INTEGER ADJ_ITER
53     LOGICAL ADJ_CONVERGED
54     #endif
55    
56    
57    
58     #ifdef ALLOW_OPENAD
59     isinloop0 =0
60     isinloop1 =1
61     isinloop2 =2
62     #endif
63    
64    
65     IF (STREAMICE_ppm_driving_stress) THEN
66     CALL STREAMICE_DRIVING_STRESS_PPM (myThid)
67     ELSE
68     CALL STREAMICE_DRIVING_STRESS (myThid)
69     ENDIF
70    
71     #ifdef STREAMICE_STRESS_BOUNDARY_CONTROL
72     _EXCH_XY_RL( taudx_SI , myThid )
73     _EXCH_XY_RL( taudy_SI , myThid )
74     CALL STREAMICE_FORCED_BUTTRESS (myThid)
75     #endif
76    
77     CALL TIMER_START ('STREAMICE_VEL_SOLVE',myThid)
78    
79     cgtol = streamice_cg_tol
80     nl_iter = 0
81     CONVERGED = .false.
82     err_last_change = 1 _d 1
83    
84     _EXCH_XY_RL( taudx_SI , myThid )
85     _EXCH_XY_RL( taudy_SI , myThid )
86    
87     #ifndef ALLOW_OPENAD
88     CALL STREAMICE_VEL_PHISTAGE (
89     I myThid,
90     I maxNLIter,
91     I maxCGiter,
92     O cgtol,
93     O nL_iter,
94     O CONVERGED,
95     O err_last_change,
96     I isinloop0)
97     #else
98     CALL STREAMICE_VEL_PHISTAGE (
99     I myThid,
100     I maxNLIter,
101     I maxCGiter,
102     O cgtol,
103     O nL_iter,
104     O adj_iter,
105     O CONVERGED,
106     O ADJ_CONVERGED,
107     O err_last_change,
108     I isinloop0)
109     #endif
110     DO bj = myByLo(myThid), myByHi(myThid)
111     DO bi = myBxLo(myThid), myBxHi(myThid)
112     DO j=1-OLy,sNy+OLy
113     DO i=1-OLx,sNx+OLx
114     U_streamice (i,j,bi,bj)=u_new_SI (i,j,bi,bj)
115     V_streamice (i,j,bi,bj)=v_new_SI (i,j,bi,bj)
116     ENDDO
117     ENDDO
118     ENDDO
119     ENDDO
120    
121     DO loopiter=1,maxNLIter
122    
123     C To avoid using "exit", loop goes through all iterations
124     C but after convergence loop does nothing
125    
126     ! IF (.not.CONVERGED) THEN
127    
128     #ifndef ALLOW_OPENAD
129     CALL STREAMICE_VEL_PHISTAGE (
130     I myThid,
131     I maxNLIter,
132     I maxCGiter,
133     O cgtol,
134     O nL_iter,
135     O CONVERGED,
136     O err_last_change,
137     I isinloop1)
138     #else
139     CALL STREAMICE_VEL_PHISTAGE (
140     I myThid,
141     I maxNLIter,
142     I maxCGiter,
143     O cgtol,
144     O nL_iter,
145     O adj_iter,
146     O CONVERGED,
147     O ADJ_CONVERGED,
148     O err_last_change,
149     I isinloop1)
150     #endif
151    
152     !DO bj = myByLo(myThid), myByHi(myThid)
153     ! DO bi = myBxLo(myThid), myBxHi(myThid)
154     ! DO j=1-OLy,sNy+OLy
155     ! DO i=1-OLx,sNx+OLx
156     ! U_streamice (i,j,bi,bj)=u_new_SI (i,j,bi,bj)
157     ! V_streamice (i,j,bi,bj)=v_new_SI (i,j,bi,bj)
158     ! ENDDO
159     ! ENDDO
160     ! ENDDO
161     !ENDDO
162    
163    
164     ENDDO
165    
166     #ifndef ALLOW_OPENAD
167     CALL STREAMICE_VEL_PHISTAGE (
168     I myThid,
169     I maxNLIter,
170     I maxCGiter,
171     O cgtol,
172     O nL_iter,
173     O CONVERGED,
174     O err_last_change,
175     I isinloop2)
176     #else
177     CALL STREAMICE_VEL_PHISTAGE (
178     I myThid,
179     I maxNLIter,
180     I maxCGiter,
181     O cgtol,
182     O nL_iter,
183     O adj_iter,
184     O CONVERGED,
185     O ADJ_CONVERGED,
186     O err_last_change,
187     I isinloop2)
188     #endif
189    
190    
191    
192     C END NL ITER. LOOP
193     C-------------------------------------------------------------------
194    
195     if (nl_iter .lt. streamice_max_nl_iter) then
196     WRITE(msgBuf,'(A,I5,A)') 'VELOCITY SOLVE CONVERGED, ',
197     & nl_iter, ' iterations'
198     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
199     & SQUEEZE_RIGHT , 1)
200     else
201     WRITE(msgBuf,'(A,I5,A)') 'VELOCITY SOLVE NOT CONVERGED IN ',
202     & nl_iter, ' iterations'
203     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
204     & SQUEEZE_RIGHT , 1)
205     endif
206    
207     _EXCH_XY_RL(U_streamice, myThid)
208     _EXCH_XY_RL(V_streamice, myThid)
209    
210     CALL TIMER_STOP ('STREAMICE_VEL_SOLVE',myThid)
211    
212     #endif
213     RETURN
214     END

  ViewVC Help
Powered by ViewVC 1.1.22