/[MITgcm]/MITgcm/pkg/autodiff/global_sum_tile_ad.F
ViewVC logotype

Contents of /MITgcm/pkg/autodiff/global_sum_tile_ad.F

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


Revision 1.3 - (show annotations) (download)
Thu Apr 22 22:23:37 2010 UTC (14 years, 1 month ago) by jmc
Branch: MAIN
Changes since 1.2: +22 -2 lines
print a warning (both to std err & outp) when current Proc input value is
different from Proc-0 value (this is suspicious given the present code).

1 C $Header: /u/gcmpack/MITgcm/pkg/autodiff/global_sum_tile_ad.F,v 1.2 2009/06/10 03:49:24 jmc Exp $
2 C $Name: $
3
4 #include "AUTODIFF_OPTIONS.h"
5
6 C-- File global_sum_tile_ad.F: Routines that perform adjoint of
7 C global sum on an array of thread values.
8 C Contents
9 C o GLOBAL_ADSUM_TILE_RL
10 C o GLOBAL_ADSUM_TILE_RS <- not yet coded
11
12 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
13 CBOP
14 C !ROUTINE: GLOBAL_ADSUM_TILE_RL
15
16 C !INTERFACE:
17 SUBROUTINE GLOBAL_ADSUM_TILE_RL(
18 O adPhiTile,
19 I adsumPhi,
20 I myThid )
21
22 C !DESCRIPTION:
23 C *==========================================================*
24 C | SUBROUTINE GLOBAL\_ADSUM\_TILE\_RL
25 C | o Handle sum for _RL data.
26 C *==========================================================*
27 C | Apply sum on an array of one value per tile
28 C | and operate over all tiles & all the processes.
29 C *==========================================================*
30
31 C !USES:
32 IMPLICIT NONE
33
34 C == Global data ==
35 #include "SIZE.h"
36 #include "EEPARAMS.h"
37 #include "EESUPPORT.h"
38 #include "GLOBAL_SUM.h"
39
40 C !INPUT/OUTPUT PARAMETERS:
41 C == Routine arguments ==
42 C phiTile :: Input array with one value per tile
43 C sumPhi :: Result of sum.
44 C myThid :: My thread id.
45 _RL adphiTile(nSx,nSy)
46 _RL adsumPhi
47 INTEGER myThid
48 CEOP
49
50 C !LOCAL VARIABLES:
51 C == Local variables ==
52 C bi,bj :: tile indices
53 C mpiRC :: MPI return code
54 INTEGER bi,bj
55 Real*8 tmp
56 #ifdef ALLOW_USE_MPI
57 INTEGER mpiRC
58 #endif /* ALLOW_USE_MPI */
59 CHARACTER*(MAX_LEN_MBUF) msgBuf
60
61 C-- Can not start until everyone is ready
62 _BARRIER
63
64 C-- broadcast to all processes
65 _BEGIN_MASTER( myThid )
66
67 tmp = adsumPhi
68
69 #ifdef ALLOW_USE_MPI
70 #ifndef ALWAYS_USE_MPI
71 IF ( usingMPI ) THEN
72 #endif
73 CALL MPI_Bcast( tmp, 1, MPI_DOUBLE_PRECISION, 0,
74 & MPI_COMM_MODEL, mpiRC )
75 #ifndef ALWAYS_USE_MPI
76 ENDIF
77 #endif
78 #endif /* ALLOW_USE_MPI */
79
80 C---- Testing stage: print a warning (both to std err & outp) when
81 C current Proc input value is different from Proc-0 value
82 IF ( tmp.NE.adsumPhi ) THEN
83 C- might need to improve this test if some MPI truncation happen
84 WRITE(msgBuf,'(A,1PE22.14)')
85 & 'GLOBAL_ADSUM_TILE_RL: ** WARNING ** input =', adsumPhi
86 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
87 & SQUEEZE_RIGHT, myThid )
88 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
89 & SQUEEZE_RIGHT, myThid )
90 WRITE(msgBuf,'(A,1PE22.14)')
91 & 'GLOBAL_ADSUM_TILE_RL: ** WARNING ** output=', tmp
92 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
93 & SQUEEZE_RIGHT, myThid )
94 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
95 & SQUEEZE_RIGHT, myThid )
96 ENDIF
97 C----
98
99 phiGSR8(1,0) = tmp
100
101 _END_MASTER( myThid )
102
103 _BARRIER
104
105 C-- every thread takes its adjoint sum
106 DO bj = myByLo(myThid), myByHi(myThid)
107 DO bi = myBxLo(myThid), myBxHi(myThid)
108 adphiTile(bi,bj) = phiGSR8(1,0)
109 ENDDO
110 ENDDO
111 C-- reset input to zero (jmc: is it right ? necessary ?)
112 c adsumPhi = 0.
113
114 RETURN
115 END

  ViewVC Help
Powered by ViewVC 1.1.22