TABLE OF CONTENTS


ABINIT/testTransposer [ Programs ]

[ Top ] [ Programs ]

NAME

 testTransposer

FUNCTION

 test the xgTransposer module with 8 MPI. No more no less.
 It includes testing of complex and real numbers, and all2all and gatherv

COPYRIGHT

 Copyright (C) 1998-2024 ABINIT group (JB)
 This file is distributed under the terms of the
 GNU General Public License, see ~abinit/COPYING
 or http://www.gnu.org/copyleft/gpl.txt .
 For the initials of contributors, see ~abinit/doc/developers/contributors.txt .

NOTES

INPUTS

  (main routine)

OUTPUT

  (main routine)

SOURCE

 26 #if defined HAVE_CONFIG_H
 27 #include "config.h"
 28 #endif
 29 
 30 #include "abi_common.h"
 31 program testTransposer
 32   use m_xg
 33   use m_xgTransposer
 34   use m_xmpi
 35   use m_time
 36   use defs_basis
 37   use m_profiling_abi
 38   use m_errors
 39 
 40   implicit none
 41 
 42   integer :: npw
 43   integer :: nband
 44   integer :: ncycle
 45   integer :: i
 46   integer :: ierr
 47   double precision :: errmax
 48   double precision :: walltime
 49   double precision :: cputime
 50   double precision :: maxt
 51   integer :: nCpuCols, nCpuRows
 52   double precision, allocatable :: cg(:,:)
 53   double precision, allocatable :: cg0(:,:)
 54   double precision, allocatable :: gh(:,:)
 55   double precision, allocatable :: ghc(:,:)
 56   character(len=40) :: names(8)
 57 
 58   double precision :: nflops, ftimes(2)
 59   integer :: ncount
 60   double precision :: times(2)
 61 
 62   type(xgBlock_t) :: xcgLinalg
 63   type(xgBlock_t) :: xcgColsRows
 64   type(xgBlock_t) :: xghLinalg
 65   type(xgBlock_t) :: xghColsRows
 66   type(xgBlock_t) :: xghcLinalg
 67   type(xgBlock_t) :: xghcColsRows
 68   type(xgTransposer_t) :: xgTransposer
 69 
 70 
 71   names(1662-1661) = 'xgTransposer_transpose@ColsRows'
 72   names(1663-1661) = 'xgTransposer_transpose@Linalg  '
 73   names(1664-1661) = 'xgTransposer_*@all2all         '
 74   names(1665-1661) = 'xgTransposer_*@gatherv         '
 75   names(1666-1661) = 'xgTransposer_@reorganize       '
 76   names(1667-1661) = 'xgTransposer_*constructor      '
 77   names(1668-1661) = 'xgTransposer_free              '
 78   names(1669-1661) = 'xgTransposer_transpose         '
 79 
 80   call xmpi_init()
 81 
 82   npw = 4000+2*xmpi_comm_rank(xmpi_world)
 83   nband = 2000
 84   ncycle = 20
 85   if ( xmpi_comm_size(xmpi_world) > 1 ) then
 86     if ( MOD(xmpi_comm_size(xmpi_world),10) == 0 ) then
 87       nCpuRows = 2
 88     else if ( MOD(xmpi_comm_size(xmpi_world),8) == 0 ) then
 89       nCpuRows = 4
 90     else if ( MOD(xmpi_comm_size(xmpi_world),6) == 0 ) then
 91       nCpuRows = 3
 92     else if ( MOD(xmpi_comm_size(xmpi_world),4) == 0 ) then
 93       nCpuRows = 2
 94     else
 95       nCpuRows = 1
 96     end if
 97     nCpuCols = xmpi_comm_size(xmpi_world)/nCpuRows
 98   else
 99     nCpuRows = 1
100     nCpuCols = 1
101   end if
102 
103   std_out = 6+xmpi_comm_rank(xmpi_world)
104 
105   write(std_out,*) " nCpuRows,nCpuCols",nCpuRows,nCpuCols
106 
107 
108  ! Initialize memory profiling if it is activated
109  ! if a full memocc.prc report is desired, set the argument of abimem_init to "2" instead of "0"
110  ! note that memocc.prc files can easily be multiple GB in size so don't use this option normally
111 #ifdef HAVE_MEM_PROFILING
112  call abimem_init(0)
113 #endif
114 
115   call test1()
116 
117   ! nspinor = 1
118   call test2(1)
119 
120   ! nspinor = 2
121   call test2(2)
122 
123   call xg_finalize()
124 
125 
126  ! Writes information on file about the memory before ending mpi module, if memory profiling is enabled
127  call abinit_doctor("__testtransposer")
128 
129   call xmpi_end()
130 
131   contains

testTransposer/backAndForth [ Functions ]

[ Top ] [ testTransposer ] [ Functions ]

NAME

 backAndForth

FUNCTION

COPYRIGHT

 Copyright (C) 1998-2024 ABINIT group (JB)
 This file is distributed under the terms of the
 GNU General Public License, see ~abinit/COPYING
 or http://www.gnu.org/copyleft/gpl.txt .
 For the initials of contributors, see ~abinit/doc/developers/contributors.txt .

NOTES

INPUTS

  (main routine)

OUTPUT

  (main routine)

SOURCE

398     subroutine backAndForth()
399 
400       maxt = 0
401       cputime = 0
402       do i=1,ncycle
403         walltime = abi_wtime()
404         call xgTransposer_transpose(xgTransposer,STATE_COLSROWS)
405         if ( ncpucols > 1 ) then ! for 1 both states are aliased !!
406           call random_number(cg)
407         end if
408         !call xgBlock_scale(xcgLinalg,0.d0,1)
409         !call xgBlock_print(xgeigen,6)
410         call xgTransposer_transpose(xgTransposer,STATE_LINALG)
411         !call xgBlock_print(xgx0,6)
412         call xmpi_barrier(xmpi_world)
413         walltime = abi_wtime() - walltime
414         cputime = cputime + walltime
415         call xmpi_max(walltime,maxt,xmpi_world,ierr)
416       end do
417       call xmpi_max(cputime,maxt,xmpi_world,ierr)
418       write(std_out,"(a,f20.5)") "-Mean time:  ", maxt/ncycle
419       errmax = (sum(abs(cg0-cg)))/nband
420       call xmpi_sum(errmax,xmpi_world,ierr)
421       write(std_out,"(a,f20.14)") " Difference: ",errmax
422       call xmpi_barrier(xmpi_world)
423     end subroutine backAndForth

testTransposer/initVectors [ Functions ]

[ Top ] [ testTransposer ] [ Functions ]

NAME

 initVectors

FUNCTION

COPYRIGHT

 Copyright (C) 1998-2024 ABINIT group (JB)
 This file is distributed under the terms of the
 GNU General Public License, see ~abinit/COPYING
 or http://www.gnu.org/copyleft/gpl.txt .
 For the initials of contributors, see ~abinit/doc/developers/contributors.txt .

NOTES

INPUTS

  (main routine)

OUTPUT

  (main routine)

SOURCE

353   subroutine initVectors()
354     integer, allocatable :: seed(:)
355     integer :: n, iseed
356     integer :: icol, irow
357 
358     call random_seed(size=n)
359     ABI_MALLOC(seed,(n))
360     do icol = 1, nband
361       do iseed = 1, n
362         seed(iseed) = (xmpi_comm_rank(xmpi_world)*nband+icol)*n+iseed
363       end do
364       call random_seed(put=seed)
365       do irow = 1, npw
366         call random_number(cg(:,(icol-1)*npw+1:icol*npw))
367         call random_number(gh(:,(icol-1)*npw+1:icol*npw))
368       end do
369     end do
370     ABI_FREE(seed)
371   end subroutine initVectors

testTransposer/printTimes [ Functions ]

[ Top ] [ testTransposer ] [ Functions ]

NAME

 printTimes

FUNCTION

COPYRIGHT

 Copyright (C) 1998-2024 ABINIT group (JB)
 This file is distributed under the terms of the
 GNU General Public License, see ~abinit/COPYING
 or http://www.gnu.org/copyleft/gpl.txt .
 For the initials of contributors, see ~abinit/doc/developers/contributors.txt .

NOTES

INPUTS

  (main routine)

OUTPUT

  (main routine)

SOURCE

450     subroutine printTimes()
451 
452       double precision :: total(2)
453       integer :: ntot
454       write(std_out,'(1x,a30,a8,a17,a17)') "counter", "calls", "cpu_time", "wall_time"
455       ntot = 0
456       total(:) = 0.d0
457       do i=1662,1669
458         call time_accu(i,ncount,times,nflops,ftimes)
459         total(1) = total(1) + times(1)
460         total(2) = total(2) + times(2)
461         ntot = ntot + ncount
462         write(std_out,'(a,a30,i8,2F17.3)') "-",trim(names(i-1661)), ncount, times(1), times(2)
463       end do
464       write(std_out,'(a,a30,i8,2F17.3)') "-","total", ntot, total(1), total(2)
465       call timab(1,0,times)
466 
467     end subroutine printTimes
468 
469 
470   end program testTransposer

testTransposer/test1 [ Functions ]

[ Top ] [ testTransposer ] [ Functions ]

NAME

 test1

FUNCTION

COPYRIGHT

 Copyright (C) 1998-2024 ABINIT group (JB)
 This file is distributed under the terms of the
 GNU General Public License, see ~abinit/COPYING
 or http://www.gnu.org/copyleft/gpl.txt .
 For the initials of contributors, see ~abinit/doc/developers/contributors.txt .

NOTES

INPUTS

  (main routine)

OUTPUT

  (main routine)

SOURCE

157   subroutine test1()
158     ABI_MALLOC(cg, (2,npw*nband))
159     ABI_MALLOC(cg0, (2,npw*nband))
160 
161     call random_number(cg)
162     cg0(:,:) = cg(:,:)
163 
164     call xgBlock_map(xcgLinalg,cg,SPACE_C,npw,nband,xmpi_world)
165 
166     write(std_out,*) " Complex all2all"
167     call xgTransposer_constructor(xgTransposer,xcgLinalg,xcgColsRows,1,&
168       STATE_LINALG,TRANS_ALL2ALL,xmpi_comm_null,xmpi_comm_null,ncpuCols,ncpuRows)
169     call backAndForth()
170     call xgTransposer_free(xgTransposer)
171     call printTimes()
172 
173     write(std_out,*) " Complex gatherv"
174     call xgTransposer_constructor(xgTransposer,xcgLinalg,xcgColsRows,1,&
175       STATE_LINALG,TRANS_GATHER,xmpi_comm_null,xmpi_comm_null,ncpuCols,ncpuRows)
176     call backAndForth()
177     call xgTransposer_free(xgTransposer)
178     call printTimes()
179 
180     call xgBlock_map(xcgLinalg,cg,SPACE_CR,2*npw,nband,xmpi_world)
181 
182     write(std_out,*) " Real all2all"
183     call xgTransposer_constructor(xgTransposer,xcgLinalg,xcgColsRows,1,&
184       STATE_LINALG,TRANS_ALL2ALL,xmpi_comm_null,xmpi_comm_null,ncpuCols,ncpuRows)
185     call backAndForth()
186     call xgTransposer_free(xgTransposer)
187     call printTimes()
188 
189     write(std_out,*) " Real gatherv"
190     call xgTransposer_constructor(xgTransposer,xcgLinalg,xcgColsRows,1,&
191       STATE_LINALG,TRANS_GATHER,xmpi_comm_null,xmpi_comm_null,ncpuCols,ncpuRows)
192     call backAndForth()
193     call xgTransposer_free(xgTransposer)
194     call printTimes()
195 
196     write(std_out,*) " Complex all2all (nspinor=2)"
197     call xgTransposer_constructor(xgTransposer,xcgLinalg,xcgColsRows,2,&
198       STATE_LINALG,TRANS_ALL2ALL,xmpi_comm_null,xmpi_comm_null,ncpuCols,ncpuRows)
199     call backAndForth()
200     call xgTransposer_free(xgTransposer)
201     call printTimes()
202 
203     write(std_out,*) " Complex gatherv (nspinor=2)"
204     call xgTransposer_constructor(xgTransposer,xcgLinalg,xcgColsRows,2,&
205       STATE_LINALG,TRANS_GATHER,xmpi_comm_null,xmpi_comm_null,ncpuCols,ncpuRows)
206     call backAndForth()
207     call xgTransposer_free(xgTransposer)
208     call printTimes()
209 
210     call xgBlock_map(xcgLinalg,cg,SPACE_CR,2*npw,nband,xmpi_world)
211 
212     write(std_out,*) " Real all2all (nspinor=2)"
213     call xgTransposer_constructor(xgTransposer,xcgLinalg,xcgColsRows,2,&
214       STATE_LINALG,TRANS_ALL2ALL,xmpi_comm_null,xmpi_comm_null,ncpuCols,ncpuRows)
215     call backAndForth()
216     call xgTransposer_free(xgTransposer)
217     call printTimes()
218 
219     write(std_out,*) " Real gatherv (nspinor=2)"
220     call xgTransposer_constructor(xgTransposer,xcgLinalg,xcgColsRows,2,&
221       STATE_LINALG,TRANS_GATHER,xmpi_comm_null,xmpi_comm_null,ncpuCols,ncpuRows)
222     call backAndForth()
223     call xgTransposer_free(xgTransposer)
224     call printTimes()
225 
226     ABI_FREE(cg)
227     ABI_FREE(cg0)
228   end subroutine test1

testTransposer/test2 [ Functions ]

[ Top ] [ testTransposer ] [ Functions ]

NAME

 test2

FUNCTION

COPYRIGHT

 Copyright (C) 1998-2024 ABINIT group (JB)
 This file is distributed under the terms of the
 GNU General Public License, see ~abinit/COPYING
 or http://www.gnu.org/copyleft/gpl.txt .
 For the initials of contributors, see ~abinit/doc/developers/contributors.txt .

NOTES

INPUTS

  (main routine)

OUTPUT

  (main routine)

SOURCE

254   subroutine test2(nspinor)
255     integer,intent(in) :: nspinor
256     type(xgTransposer_t) :: xgTransposerGh
257     type(xgTransposer_t) :: xgTransposerGhc
258     type(xg_t) :: dotLinalg
259     type(xg_t) :: dotColsRows
260     double precision :: maxdiff
261 
262     write(std_out,*) "Allocation"
263     ABI_MALLOC(cg,(2,npw*nband))
264     ABI_MALLOC(gh,(2,npw*nband))
265     ABI_MALLOC(ghc,(2,npw*nband))
266 
267     write(std_out,*) "Mapping"
268     call xgBlock_map(xcgLinalg,cg,SPACE_C,npw,nband,xmpi_world)
269     call xgBlock_map(xghLinalg,gh,SPACE_C,npw,nband,xmpi_world)
270     call xgBlock_map(xghcLinalg,ghc,SPACE_C,npw,nband,xmpi_world)
271 
272     write(std_out,*) "Transposer constructor : nspinor =",nspinor
273 
274     call xgTransposer_constructor(xgTransposer,xcgLinalg,xcgColsRows,nspinor,&
275       STATE_LINALG,TRANS_ALL2ALL,xmpi_comm_null,xmpi_comm_null,ncpuCols,ncpuRows)
276     call xgTransposer_copyConstructor(xgTransposerGh,xgTransposer,xghLinalg,xghColsRows,STATE_LINALG)
277     call xgTransposer_copyConstructor(xgTransposerGhc,xgTransposer,xghcLinalg,xghcColsRows,STATE_LINALG)
278 
279     write(std_out,*) "Init data"
280     call random_number(cg)
281     call random_number(gh)
282     !call initVectors()
283 
284     write(std_out,*) "Linalg division"
285     call xgBlock_colwiseDivision(xcgLinalg,xghLinalg,xghcLinalg)
286 
287     write(std_out,*) "Linalg norm2"
288     call xg_init(dotLinalg,SPACE_R,nband,1,xmpi_world)
289     call xgBlock_colwiseNorm2(xghcLinalg,dotLinalg%self)
290     !call xgBlock_print(dotLinalg%self,std_out)
291 
292     write(std_out,*) "Transposer transpose"
293     call xgTransposer_transpose(xgTransposer,STATE_COLSROWS)
294     call xgTransposer_transpose(xgTransposerGh,STATE_COLSROWS)
295     call xgTransposer_transpose(xgTransposerGhc,STATE_COLSROWS)
296 
297     write(std_out,*) "ColsRows divisions"
298     call xgBlock_colwiseDivision(xcgColsRows,xghColsRows,xghcColsRows)
299 
300     write(std_out,*) "Transposer transpose back"
301     call xgTransposer_transpose(xgTransposerGhc,STATE_LINALG)
302 
303     write(std_out,*) "ColsRows norm2"
304     call xg_init(dotColsRows,SPACE_R,nband,1,xmpi_world)
305     call xgBlock_colwiseNorm2(xghcLinalg,dotColsRows%self)
306     !call xgBlock_print(dotColsRows%self,std_out)
307 
308     write(std_out,*) "Compare"
309     call xgBlock_saxpy(dotLinalg%self, -1.0d0, dotColsRows%self)
310     call xgBlock_reshape(dotLinalg%self, (/1,nband/))
311     call xgBlock_colwiseNorm2(dotLinalg%self,dotColsRows%self,max_val=maxdiff)
312     write(std_out,"(a,f20.4)") " Difference: ",sqrt(maxdiff)
313 
314     write(std_out,*) "Free everything"
315     call xg_free(dotLinalg)
316     call xg_free(dotColsRows)
317 
318     call xgTransposer_free(xgTransposer)
319     call xgTransposer_free(xgTransposerGh)
320     call xgTransposer_free(xgTransposerGhc)
321 
322     ABI_FREE(cg)
323     ABI_FREE(gh)
324     ABI_FREE(ghc)
325 
326   end subroutine test2