TABLE OF CONTENTS


ABINIT/m_initcuda [ Modules ]

[ Top ] [ Modules ]

NAME

 m_initcuda

FUNCTION

  Module containing all variables concerning GPU device
  and the functions needed to extract them

COPYRIGHT

  Copyright (C) 2009-2018 ABINIT group (MMancini, MT, FDahm)
  This file is distributed under the terms of the
  GNU General Public License, see ~abinit/COPYING
  or http://www.gnu.org/copyleft/gpl.txt .

NOTES

  Is an experimental development

PARENTS

CHILDREN

SOURCE

25 #if defined HAVE_CONFIG_H
26 #include "config.h"
27 #endif
28 
29 #if defined HAVE_GPU_CUDA
30 #include "cuda_common.h"
31 #endif
32 
33 #include "abi_common.h"
34 
35 module m_initcuda
36 
37  use defs_basis
38  use m_abicore
39  use m_xmpi, only: xmpi_world,xmpi_comm_rank,xmpi_comm_size,xmpi_abort
40 
41  implicit none
42 
43 #if defined HAVE_GPU_CUDA
44  integer,parameter,public :: cudap=kind(CUDA_KIND)
45 #endif
46 
47 !Structures

m_initcuda/CleanGPU [ Functions ]

[ Top ] [ m_initcuda ] [ Functions ]

NAME

 CleanGPU

FUNCTION

 Print information about GPU device

PARENTS

      m_hidecudarec,m_initcuda

CHILDREN

SOURCE

305  subroutine CleanGPU(gpuinfo)
306 
307 
308 !This section has been created automatically by the script Abilint (TD).
309 !Do not modify the following lines by hand.
310 #undef ABI_FUNC
311 #define ABI_FUNC 'CleanGPU'
312 !End of the abilint section
313 
314  implicit none
315 
316 !Arguments ------------------------------------
317 !scalars
318  type(devGPU_type),intent(inout) :: gpuinfo
319 ! *********************************************************************
320 #if defined HAVE_GPU_CUDA
321  if (allocated(gpuinfo%maxmemdev))  then
322    ABI_DEALLOCATE(gpuinfo%maxmemdev)
323  end if
324 #endif
325 
326  end subroutine CleanGPU

m_initcuda/devGPU_type [ Types ]

[ Top ] [ m_initcuda ] [ Types ]

NAME

 devGPU_type

FUNCTION

 This structured datatype used to contains GPU properties

SOURCE

59  type,public :: devGPU_type
60   integer :: ndevice  !--number of available devices
61   real(dp),allocatable :: maxmemdev(:)  !--max global memory on any device
62  end type devGPU_type

m_initcuda/get_fastest_devices [ Functions ]

[ Top ] [ m_initcuda ] [ Functions ]

NAME

 get_fastest_devices

FUNCTION

 In case of multiple devices, sort them by performances
 and output the resulting list of devices.

PARENTS

      m_initcuda

CHILDREN

SOURCE

492  subroutine get_fastest_devices(devices,nb_devices)
493 
494 
495 !This section has been created automatically by the script Abilint (TD).
496 !Do not modify the following lines by hand.
497 #undef ABI_FUNC
498 #define ABI_FUNC 'get_fastest_devices'
499 !End of the abilint section
500 
501  implicit none
502 
503 !Arguments ------------------------------------
504 !scalars
505  integer,intent(in) :: nb_devices
506  integer,intent(out) :: devices(:)
507 !Local variables ------------------------------
508 !scalars
509  integer :: ii,nproc
510  character(len=500) :: msg
511 #if defined HAVE_GPU_CUDA
512  integer :: constmem,gflops,jj,lenname,nprocs,ncores,regist,sharemem
513  real(sp) :: clockRate,globalmem
514  character(len=20) :: name
515 #endif
516 !arrays
517 #if defined HAVE_GPU_CUDA
518  integer :: vers(0:1)
519  integer,allocatable :: isort(:)
520  real(dp),allocatable :: flops(:),mem(:)
521 #endif
522 
523 ! *********************************************************************
524 
525  nproc=xmpi_comm_size(xmpi_world)
526  if (size(devices)/=nproc) stop 'wrong size for devices array!'
527 
528 !Default
529  do ii=0,nproc-1
530    devices(ii+1) = MOD(ii,nb_devices)
531  end do
532  if (nb_devices==1) return
533 
534  write(msg,'(a,i2,a)') ch10,nb_devices,' GPU device(s) have been detected on the current node:'
535  call wrtout(std_out,msg,'PERS')
536 
537 #if defined HAVE_GPU_CUDA
538 !Check device(s) properties
539  ABI_ALLOCATE(flops,(nb_devices))
540  ABI_ALLOCATE(mem,  (nb_devices))
541  do ii=0,nb_devices-1
542    call set_dev(ii)
543    call get_dev_info(ii,name,lenname,vers,globalmem,clockRate,gflops,constmem,&
544 &                    sharemem,regist,nprocs,ncores)
545    flops(ii+1)=dble(gflops) ; mem(ii+1)=dble(globalmem)
546    call unset_dev()
547    write(msg,'(a,i2,3a,i1,a,i1,a,i6,a,f7.1,a,i7,a,i2,a,i4,a)') &
548 &   '  Device ',ii,': ',trim(name(1:lenname)),', v',vers(0),'.',vers(1),', Mem=',nint(globalmem),&
549 &   ' Mbytes, Clock=',clockrate,' GHz, ',gflops,' GFLOPS, ',nprocs,' processors, ',ncores,' cores'
550    call wrtout(std_out,msg,'PERS')
551  end do
552 
553 !Sort devices (first by flops, then by memory)
554  ABI_ALLOCATE(isort,(nb_devices))
555  isort(:)=(/(ii,ii=1,nb_devices)/)
556  call my_sort(flops,mem,isort)
557 
558 !Distribute cards among procs
559  do ii=0,nproc-1
560    jj=MOD(ii,nb_devices)
561    devices(ii+1) = isort(jj+1)-1
562  end do
563 
564  ABI_DEALLOCATE(isort)
565  ABI_DEALLOCATE(flops)
566  ABI_DEALLOCATE(mem)
567 #endif
568 
569 contains

m_initcuda/Get_Mem_Dev [ Functions ]

[ Top ] [ m_initcuda ] [ Functions ]

NAME

 Get_Mem_Dev

FUNCTION

 Get the max memory availeble on device

INPUTS

 device  device number

OUTPUT

 max_mem_dev

PARENTS

CHILDREN

SOURCE

267 subroutine Get_Mem_Dev(device,max_mem_dev)
268 
269 
270 !This section has been created automatically by the script Abilint (TD).
271 !Do not modify the following lines by hand.
272 #undef ABI_FUNC
273 #define ABI_FUNC 'Get_Mem_Dev'
274 !End of the abilint section
275 
276  implicit none
277 
278 !Arguments ------------------------------------
279 !scalars
280  integer,intent(in) :: device
281  real(sp),intent(out) :: max_mem_dev
282 !Local variables ------------------------------
283 ! *********************************************************************
284 #if defined HAVE_GPU_CUDA
285  call get_GPU_max_mem(device,max_mem_dev)
286 #endif
287 end subroutine Get_Mem_Dev

m_initcuda/InitGPU [ Functions ]

[ Top ] [ m_initcuda ] [ Functions ]

NAME

 InitGPU

FUNCTION

 Print information about GPU device

PARENTS

      m_hidecudarec,m_initcuda

CHILDREN

SOURCE

176  subroutine InitGPU(gpuinfo,device)
177 
178 
179 !This section has been created automatically by the script Abilint (TD).
180 !Do not modify the following lines by hand.
181 #undef ABI_FUNC
182 #define ABI_FUNC 'InitGPU'
183 !End of the abilint section
184 
185  implicit none
186 
187 !Arguments ------------------------------------
188 !scalars
189  integer,intent(in)              :: device
190  type(devGPU_type),intent(inout) :: gpuinfo
191 !Local variables ------------------------------
192 !scalars
193  real(sp) :: locmax
194 ! *********************************************************************
195  gpuinfo%ndevice = 0
196 #if defined HAVE_GPU_CUDA
197 !--Initialization
198  if(device>-1)then
199    !--Get the number of device for this proc
200    gpuinfo%ndevice = 1
201    ABI_ALLOCATE(gpuinfo%maxmemdev,(0:1))
202    call get_GPU_max_mem(device,locmax)
203    gpuinfo%maxmemdev(0:1) = locmax
204    call  prt_device_info(device)
205  endif
206 #endif
207  end subroutine InitGPU

m_initcuda/my_sort [ Functions ]

[ Top ] [ m_initcuda ] [ Functions ]

NAME

 my_sort

FUNCTION

  Small sorting routine: change iperm array
  according to list1 values then list2 values

PARENTS

      m_initcuda

CHILDREN

SOURCE

587  subroutine my_sort(list1,list2,iperm)
588 
589 
590 !This section has been created automatically by the script Abilint (TD).
591 !Do not modify the following lines by hand.
592 #undef ABI_FUNC
593 #define ABI_FUNC 'my_sort'
594 !End of the abilint section
595 
596  implicit none
597 
598 !Arguments ------------------------------------
599 !scalars
600  integer,intent(inout) :: iperm(:)
601  real(dp),intent(in) :: list1(:),list2(:)
602 !Local variables ------------------------------
603 !scalars
604  integer :: ll,mm,nn,pp
605  real(dp) :: xx
606 !arrays
607  real(dp),allocatable :: llist(:)
608 
609 ! *********************************************************************
610 
611  nn=size(iperm)
612  ABI_ALLOCATE(llist,(nn))
613  llist(:)=list1(:)
614  do ll=1,nn-1
615    do mm=ll+1,nn
616      if (llist(mm)>llist(ll)) then
617        xx=llist(ll);llist(ll)=llist(mm);llist(mm)=xx
618        pp=iperm(ll);iperm(ll)=iperm(mm);iperm(mm)=pp
619      end if
620    end do
621  end do
622  do ll=1,nn-1
623    do mm=ll+1,nn
624      if (abs(llist(mm)-llist(ll))<tol8) then
625        if (list2(iperm(mm))>list2(iperm(ll))) then
626          xx=llist(ll);llist(ll)=llist(mm);llist(mm)=xx
627          pp=iperm(ll);iperm(ll)=iperm(mm);iperm(mm)=pp
628        end if
629      end if
630    end do
631  end do
632  ABI_DEALLOCATE(llist)
633 
634  end subroutine my_sort

m_initcuda/prt_device_info [ Functions ]

[ Top ] [ m_initcuda ] [ Functions ]

NAME

 prt_device_info

FUNCTION

 Print information about GPU device

PARENTS

      m_initcuda

CHILDREN

SOURCE

 98  subroutine prt_device_info(device)
 99 
100 
101 !This section has been created automatically by the script Abilint (TD).
102 !Do not modify the following lines by hand.
103 #undef ABI_FUNC
104 #define ABI_FUNC 'prt_device_info'
105 !End of the abilint section
106 
107   implicit none
108 !Arguments ------------------------------------
109 !scalars
110  integer,intent(in) :: device
111 !Local variables ------------------------------
112 !scalars
113  integer :: gflops,constmem,sharemem
114  integer :: ii,regist,lenname,ncores,nprocs
115  real(sp) :: globalmem,clockRate
116  character(20)  :: name
117  character(20)  :: formatdev
118  character(60)  :: gflops_stg
119  character(500) :: msg
120 !arrays
121  integer :: vers(0:1)
122 ! *********************************************************************
123 #if defined HAVE_GPU_CUDA
124  write(msg,'(a,80a)')' ',('_',ii=1,80)
125  call wrtout(std_out,msg,'PERS')
126  write(msg,'(a25,a25,a31,a)')  '________________________',&
127 &  ' Graphic Card Properties ','_______________________________' ,ch10
128  call wrtout(std_out,msg,'PERS')
129 
130  call get_dev_info(device,name,lenname,vers,globalmem,clockRate,gflops,constmem,sharemem,regist,nprocs,ncores)
131  if (gflops<0) then
132    gflops_stg="undefined (add new def. in version_2_cores function)"
133  else
134    write(gflops_stg,'(i7,a)') gflops,' GFP'
135  end if
136 
137  write(formatdev,'(a12,i4,a)'),'(a23,i4,a3,a',lenname,')'
138  write (msg,formatdev)&
139        & '  Device             ',device,' : ',name(1:lenname)
140  call wrtout(std_out,msg,'PERS')
141  write (msg,'(a,2(i1,a),a,i6,a,a,a,f7.1,a,a,a,i2,a,i4,4a,2(a,i7,2a),a,i7,a)')&
142        & ' Revision number:                   ',vers(0),'.',vers(1),ch10, &
143        & ' Total amount of global memory: ',nint(globalmem),' Mbytes',ch10, &
144        & ' Clock rate:                    ',clockRate,' GHz',ch10, &
145        & ' Number of processors/cores:    ',nprocs,'/',ncores,ch10, &
146        & ' Max GFLOPS:                    ',trim(gflops_stg),ch10, &
147        & ' Total  constant memory:        ',constmem,' bytes',ch10, &
148        & ' Shared memory per block:       ',sharemem,' bytes',ch10, &
149        & ' Number of registers per block: ',regist,ch10
150  call wrtout(std_out,msg,'PERS')
151  if(device == -1)then
152    write(msg,'(a)')' no cuda-GPU devices found'
153    call wrtout(std_out,msg,'PERS')
154  end if
155  write(msg,'(a,80a)')' ',('_',ii=1,80)
156  call wrtout(std_out,msg,'PERS')
157 #endif
158  end subroutine prt_device_info

m_initcuda/setdevice_cuda [ Functions ]

[ Top ] [ m_initcuda ] [ Functions ]

NAME

 setdevice_cuda

FUNCTION

 Detect and activate a GPU device from current CPU core

INPUTS

  gpu_devices(5)= list of GPU devices to choose on one node (in case of multiple devices);
                  if set to 5*-1, will choose the devices by order of performances.

SIDE EFFECTS

  use_gpu_cuda= 1 if CUDA is on; will be set to 0 if no GPU device is free.

PARENTS

      abinit

CHILDREN

SOURCE

351  subroutine setdevice_cuda(gpu_devices_node,use_gpu_cuda)
352 
353 #ifdef FC_NAG
354  use f90_unix_proc
355 #endif
356 
357 !This section has been created automatically by the script Abilint (TD).
358 !Do not modify the following lines by hand.
359 #undef ABI_FUNC
360 #define ABI_FUNC 'setdevice_cuda'
361 !End of the abilint section
362 
363  implicit none
364 
365 !Arguments ------------------------------------
366 !scalars
367  integer,intent(inout) :: use_gpu_cuda
368 !arrays
369  integer, intent(in) :: gpu_devices_node(5)
370 !Local variables ------------------------------
371 !scalars
372  integer :: device,ii,jj,me,nb_devices,nproc
373  logical :: testopen
374  character(len=500) :: msg
375  type(devGPU_type) :: gpuinfo
376 !arrays
377  integer,allocatable :: fastest_devices(:)
378 ! *********************************************************************
379 
380  if (use_gpu_cuda==0) return
381 
382  nproc=xmpi_comm_size(xmpi_world)
383  me=xmpi_comm_rank(xmpi_world)
384 
385 #if defined HAVE_GPU_CUDA
386  device=-1
387  call c_get_ndevice(nb_devices)
388  nb_devices=min(nb_devices,5)
389  if(nb_devices>0) then
390    if(nb_devices==1) then
391      device=0
392    else if(all(gpu_devices_node(1:nb_devices)==-1)) then
393      ABI_ALLOCATE(fastest_devices,(0:nproc-1))
394      call get_fastest_devices(fastest_devices,nb_devices)
395      device=fastest_devices(me)
396      ABI_DEALLOCATE(fastest_devices)
397    else
398      jj=nb_devices
399      do ii=jj,2,-1
400        if(gpu_devices_node(ii)==-1) nb_devices=ii-1
401      end do
402      device=gpu_devices_node(1+mod(me,nb_devices))
403    end if
404    call set_dev(device)
405    call check_context(nb_devices,msg)
406    if(nb_devices==1) then !allocation succeed
407      write(msg, '(4a,i1,2a)' ) ch10,&
408 &     ' setdevice_cuda : COMMENT -',ch10,&
409 &     '  GPU ',device,' has been properly initialized, continuing...',ch10
410      call wrtout(std_out,msg,'PERS')
411    else !gpu allocation failed we print error message returned and exit
412      device=-1
413      call wrtout(std_out,msg,'COLL')
414      call xmpi_abort()
415      inquire(std_out,OPENED=testopen)
416      if (testopen) close(std_out)
417 #if defined FC_NAG
418      call exit(-1)
419 #elif defined HAVE_FC_EXIT
420      call exit(1)
421 #else
422       stop 1
423 #endif
424    end if
425    call InitGPU(gpuinfo,device)
426    call CleanGPU(gpuinfo)
427  else
428    use_gpu_cuda=0
429  end if
430 #endif
431  end subroutine setdevice_cuda

m_initcuda/unsetdevice_cuda [ Functions ]

[ Top ] [ m_initcuda ] [ Functions ]

NAME

 unsetdevice_cuda

FUNCTION

 Deactivate a GPU device from current CPU core

PARENTS

      abinit

CHILDREN

SOURCE

449  subroutine unsetdevice_cuda(use_gpu_cuda)
450 
451 
452 !This section has been created automatically by the script Abilint (TD).
453 !Do not modify the following lines by hand.
454 #undef ABI_FUNC
455 #define ABI_FUNC 'unsetdevice_cuda'
456 !End of the abilint section
457 
458  implicit none
459 
460 !Arguments ------------------------------------
461 !scalars
462  integer,intent(in) :: use_gpu_cuda
463 !Local variables ------------------------------
464 !scalars
465  character(len=500) :: msg
466 ! *********************************************************************
467 
468  if (use_gpu_cuda==0) return
469 
470 #if defined HAVE_GPU_CUDA
471  call unset_dev()
472 #endif
473  end subroutine unsetdevice_cuda