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

Contents of /MITgcm_contrib/dgoldberg/streamice/streamice_get_vel_resid_err.F

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


Revision 1.1 - (show annotations) (download)
Wed Aug 27 19:29:14 2014 UTC (10 years, 11 months ago) by dgoldberg
Branch: MAIN
CVS Tags: HEAD
updating contrib streamice repo with latest files, and separated out convergence checks; and parameterised maximum iteration counts and interface w shelfice for coupling

1 C $Header: /u/gcmpack/MITgcm/pkg/streamice/streamice_vel_solve.F,v 1.7 2014/04/24 12:01:50 dgoldberg Exp $
2 C $Name: $
3
4 #include "STREAMICE_OPTIONS.h"
5
6 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
7
8 CBOP
9 SUBROUTINE STREAMICE_GET_VEL_RESID_ERR ( err_max, myThid )
10 C /============================================================\
11 C | SUBROUTINE |
12 C | o |
13 C |============================================================|
14 C | |
15 C \============================================================/
16 IMPLICIT NONE
17
18 C === Global variables ===
19 #include "SIZE.h"
20 #include "EEPARAMS.h"
21 #include "PARAMS.h"
22 #include "STREAMICE.h"
23 #include "STREAMICE_CG.h"
24 !#ifdef ALLOW_PETSC
25 !#include "finclude/petsc.h"
26 !#endif
27
28 #ifdef ALLOW_AUTODIFF_TAMC
29 # include "tamc.h"
30 #endif
31
32 C !INPUT/OUTPUT ARGUMENTS
33 _RL err_max
34 INTEGER myThid, myiter
35
36 #ifdef ALLOW_STREAMICE
37
38 INTEGER conv_flag, i, j, bi, bj
39
40 INTEGER ikey_nl
41 _RL err_tempu, err_tempv
42 _RL max_vel, tempu, tempv, err_lastchange, cgtol
43 CHARACTER*(MAX_LEN_MBUF) msgBuf
44
45 !#ifdef ALLOW_AUTODIFF_TAMC
46 !!$TAF STORE U_streamice = comlev1_stream_nl, key=ikey_nl
47 !!$TAF STORE V_streamice = comlev1_stream_nl, key=ikey_nl
48 !#endif
49
50
51
52 err_max = 0. _d 0
53
54 DO bj = myByLo(myThid), myByHi(myThid)
55 DO bi = myBxLo(myThid), myBxHi(myThid)
56 DO j=1,sNy
57 DO i=1,sNx
58 Au_SI (i,j,bi,bj) = 0. _d 0
59 Av_SI (i,j,bi,bj) = 0. _d 0
60 ubd_SI (i,j,bi,bj) = 0. _d 0
61 vbd_SI (i,j,bi,bj) = 0. _d 0
62 ENDDO
63 ENDDO
64 ENDDO
65 ENDDO
66
67 CALL STREAMICE_CG_BOUND_VALS( myThid,
68 O ubd_SI,
69 O vbd_SI)
70
71 !#ifdef ALLOW_AUTODIFF_TAMC
72 !!$TAF STORE U_streamice = comlev1_stream_nl, key=ikey_nl
73 !!$TAF STORE V_streamice = comlev1_stream_nl, key=ikey_nl
74 !#endif
75
76 CALL STREAMICE_CG_ACTION( myThid,
77 O Au_SI,
78 O Av_SI,
79 I U_streamice,
80 I V_streamice,
81 I 0, sNx+1, 0, sNy+1 )
82
83
84 !#ifdef ALLOW_AUTODIFF_TAMC
85 !!$TAF STORE U_streamice = comlev1_stream_nl, key=ikey_nl
86 !!$TAF STORE V_streamice = comlev1_stream_nl, key=ikey_nl
87 !#endif
88
89 DO bj = myByLo(myThid), myByHi(myThid)
90 DO bi = myBxLo(myThid), myBxHi(myThid)
91 DO j=1,sNy
92 DO i=1,sNx
93 err_tempu = 0. _d 0
94 err_tempv = 0. _d 0
95 IF (STREAMICE_umask(i,j,bi,bj).eq.1) THEN
96 err_tempu =
97 & ABS (Au_SI(i,j,bi,bj)+0*ubd_SI(i,j,bi,bj) -
98 & taudx_SI(i,j,bi,bj))
99 ENDIF
100 IF (STREAMICE_vmask(i,j,bi,bj).eq.1) THEN
101 err_tempv = MAX( err_tempu,
102 & ABS (Av_SI(i,j,bi,bj)+0*vbd_SI(i,j,bi,bj) -
103 & taudy_SI(i,j,bi,bj)))
104 ENDIF
105 IF (err_tempv .ge. err_max) THEN
106 err_max = err_tempv
107 ENDIF
108 ENDDO
109 ENDDO
110 ENDDO
111 ENDDO
112
113 CALL GLOBAL_MAX_R8 (err_max, myThid)
114 !#ifdef ALLOW_AUTODIFF_TAMC
115 !!$TAF STORE err_max = comlev1_stream_nl, key=ikey_dynamics
116 !#endif
117
118 #endif
119 RETURN
120 END

  ViewVC Help
Powered by ViewVC 1.1.22