/[MITgcm]/MITgcm/pkg/streamice/streamice_get_vel_resid_err_oad.F
ViewVC logotype

Contents of /MITgcm/pkg/streamice/streamice_get_vel_resid_err_oad.F

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


Revision 1.2 - (show annotations) (download)
Mon Mar 23 14:07:16 2015 UTC (9 years, 2 months ago) by dgoldberg
Branch: MAIN
CVS Tags: checkpoint65r, checkpoint65s, checkpoint65p, checkpoint65q, checkpoint65t, checkpoint65u, checkpoint65k, checkpoint65n, checkpoint65o, checkpoint65l, checkpoint65m
Changes since 1.1: +14 -24 lines
further changes to allow for residual convergence check with christianson f.p. algorithm,
and to allow for the PHI() format of calling vel_solve() without openad

1 C $Header: /u/gcmpack/MITgcm/pkg/streamice/streamice_get_vel_resid_err_oad.F,v 1.1 2015/03/02 18:11:58 dgoldberg Exp $
2 C $Name: $
3
4 #include "STREAMICE_OPTIONS.h"
5 #ifdef ALLOW_AUTODIFF
6 # include "AUTODIFF_OPTIONS.h"
7 #endif
8
9
10 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
11
12 CBOP
13 SUBROUTINE STREAMICE_GET_VEL_RESID_ERR_OAD ( err_max, myThid )
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 C !INPUT/OUTPUT ARGUMENTS
30 _RL err_max
31 INTEGER myThid
32 Real*8 u_dummy (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
33 Real*8 v_dummy (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
34
35 #ifdef ALLOW_STREAMICE
36 #if (defined (ALLOW_STREAMICE_OAD_FP))
37
38 INTEGER conv_flag, i, j, bi, bj, myIter
39
40
41 INTEGER ikey_nl
42 _RL err_tempu, err_tempv
43 _RL max_vel, tempu, tempv, err_lastchange, cgtol
44 CHARACTER*(MAX_LEN_MBUF) msgBuf
45 LOGICAL isTape
46
47 err_max = 0. _d 0
48
49 DO bj = myByLo(myThid), myByHi(myThid)
50 DO bi = myBxLo(myThid), myBxHi(myThid)
51 DO j=1-oly,sNy+oly
52 DO i=1-olx,sNx+olx
53 Au_SI (i,j,bi,bj) = 0. _d 0
54 Av_SI (i,j,bi,bj) = 0. _d 0
55 u_dummy (i,j,bi,bj) = u_streamice(i,j,bi,bj)
56 v_dummy (i,j,bi,bj) = v_streamice(i,j,bi,bj)
57 ubd_SI (i,j,bi,bj) = 0. _d 0
58 vbd_SI (i,j,bi,bj) = 0. _d 0
59 ENDDO
60 ENDDO
61 ENDDO
62 ENDDO
63
64 CALL STREAMICE_CG_BOUND_VALS( myThid,
65 O ubd_SI,
66 O vbd_SI)
67
68 CALL STREAMICE_CG_ACTION( myThid,
69 O Au_SI,
70 O Av_SI,
71 I U_dummy,
72 I V_dummy,
73 I 0, sNx+1, 0, sNy+1 )
74
75
76 DO bj = myByLo(myThid), myByHi(myThid)
77 DO bi = myBxLo(myThid), myBxHi(myThid)
78 DO j=1,sNy
79 DO i=1,sNx
80 err_tempu = 0. _d 0
81 err_tempv = 0. _d 0
82 IF (STREAMICE_umask(i,j,bi,bj).eq.1) THEN
83 err_tempu =
84 & ABS (Au_SI(i,j,bi,bj)+0*ubd_SI(i,j,bi,bj) -
85 & taudx_SI(i,j,bi,bj))
86 ENDIF
87 IF (STREAMICE_vmask(i,j,bi,bj).eq.1) THEN
88 err_tempv = MAX( err_tempu,
89 & ABS (Av_SI(i,j,bi,bj)+0*vbd_SI(i,j,bi,bj) -
90 & taudy_SI(i,j,bi,bj)))
91 ENDIF
92 IF (err_tempv .ge. err_max) THEN
93 err_max = err_tempv
94 ENDIF
95 ENDDO
96 ENDDO
97 ENDDO
98 ENDDO
99
100
101
102 CALL GLOBAL_MAX_R8 (err_max, myThid)
103
104 #endif
105 #endif
106 RETURN
107 END

  ViewVC Help
Powered by ViewVC 1.1.22