New URL for NEMO forge!   http://forge.nemo-ocean.eu

Since March 2022 along with NEMO 4.2 release, the code development moved to a self-hosted GitLab.
This present forge is now archived and remained online for history.
mpp_loc_generic.h90 in NEMO/branches/2018/dev_r10164_HPC09_ESIWACE_PREP_MERGE/src/OCE/LBC – NEMO

source: NEMO/branches/2018/dev_r10164_HPC09_ESIWACE_PREP_MERGE/src/OCE/LBC/mpp_loc_generic.h90 @ 10314

Last change on this file since 10314 was 10314, checked in by smasson, 5 years ago

dev_r10164_HPC09_ESIWACE_PREP_MERGE: action 2: add generic glob_min/max/sum and locmin/max, complete timing and report (including bdy and icb), see #2133

File size: 3.2 KB
Line 
1                          !==  IN: ptab is an array  ==!
2#      define ARRAY_TYPE(i,j,k)    REAL(wp)          , INTENT(in   ) ::   ARRAY_IN(i,j,k)
3#      define MASK_TYPE(i,j,k)     REAL(wp)          , INTENT(in   ) ::   MASK_IN(i,j,k)
4#   if defined DIM_2d
5#      define ARRAY_IN(i,j,k)   ptab(i,j)
6#      define MASK_IN(i,j,k)    pmask(i,j)
7#      define INDEX_TYPE(k)        INTEGER           , INTENT(  out) ::   kindex(2)
8#      define K_SIZE(ptab)      1
9#   endif
10#   if defined DIM_3d
11#      define ARRAY_IN(i,j,k)   ptab(i,j,k)
12#      define MASK_IN(i,j,k)    pmask(i,j,k)
13#      define INDEX_TYPE(k)        INTEGER           , INTENT(  out) ::   kindex(3)
14#      define K_SIZE(ptab)      SIZE(ptab,3)
15#   endif
16#   if defined OPERATION_MAXLOC
17#      define MPI_OPERATION mpi_maxloc
18#   endif
19#   if defined OPERATION_MINLOC
20#      define MPI_OPERATION mpi_minloc
21#   endif
22
23   SUBROUTINE ROUTINE_LOC( cdname, ptab, pmask, pmin, kindex )
24      !!----------------------------------------------------------------------
25      CHARACTER(len=*), INTENT(in   ) ::   cdname  ! name of the calling subroutine
26      ARRAY_TYPE(:,:,:)                                ! array on which loctrans operation is applied
27      MASK_TYPE(:,:,:)                                 ! local mask
28      REAL(wp)        , INTENT(  out) ::   pmin    ! Global minimum of ptab
29      INDEX_TYPE(:)                                ! index of minimum in global frame
30# if defined key_mpp_mpi
31      !
32      INTEGER  ::   ierror, ii, idim
33      REAL(wp) ::   zmin     ! local minimum
34      INTEGER , DIMENSION(:), ALLOCATABLE  ::   ilocs
35      REAL(wp), DIMENSION(2,1) ::   zain, zaout
36      !!-----------------------------------------------------------------------
37      !
38      IF( narea == 1 .AND. numcom == -1 ) CALL mpp_report( cdname, ld_glb = .TRUE. )
39      !
40      idim = SIZE(kindex)
41      ALLOCATE ( ilocs(idim) )
42      !
43      zmin  = MINVAL( ARRAY_IN(:,:,:) , mask= MASK_IN(:,:,:) == 1._wp )
44      ilocs = MINLOC( ARRAY_IN(:,:,:) , mask= MASK_IN(:,:,:) == 1._wp )
45      !
46      DO ii = 1, idim
47        IF (ii == 1) kindex(1) = ilocs(1) + nimpp - 1
48        IF (ii == 2) kindex(2) = ilocs(2) + njmpp - 1
49        IF (ii == 3) kindex(3) = ilocs(3)
50      ENDDO
51      !
52      DEALLOCATE (ilocs)
53      !
54      zain(1,:) = zmin
55      zain(2,:) = kindex(1) + 10000.* kindex(2)
56      IF ( idim == 3) zain(2,:) = zain(2,:) + 100000000.*kindex(3)
57      !
58      IF( ln_timing ) CALL tic_tac(.TRUE., ld_global = .TRUE.)
59      CALL MPI_ALLREDUCE( zain, zaout, 1, MPI_2DOUBLE_PRECISION, MPI_OPERATION ,MPI_COMM_OCE, ierror)
60      IF( ln_timing ) CALL tic_tac(.FALSE., ld_global = .TRUE.)
61      !
62      pmin = zaout(1,1)
63      IF ( idim == 3) THEN
64        kindex(3)   = INT( zaout(2,1) / 100000000. )
65        kindex(2)   = INT( zaout(2,1) - kindex(3) * 100000000. ) / 10000
66        kindex(1)   = INT( zaout(2,1) - kindex(3) * 100000000. -kindex(2) * 10000. )
67      ELSE
68        kindex(2)   = INT( zaout(2,1) / 10000 )
69        kindex(1)   = INT( zaout(2,1) -kindex(2) * 10000. )
70      ENDIF
71#else
72      kindex = 0 ; pmin = 0.
73      WRITE(*,*) 'ROUTINE_LOC: You should not have seen this print! error?'
74#endif
75
76   END SUBROUTINE ROUTINE_LOC
77
78#undef ARRAY_TYPE
79#undef MAX_TYPE
80#undef ARRAY_IN
81#undef MASK_IN
82#undef K_SIZE
83#undef MPI_OPERATION
84#undef INDEX_TYPE
Note: See TracBrowser for help on using the repository browser.