Skip to content

Commit 0e89509

Browse files
committed
Merge branch 'stage-1.2' into release
2 parents 2158eed + ba5a9fb commit 0e89509

File tree

8 files changed

+266
-23
lines changed

8 files changed

+266
-23
lines changed

CHANGELOG.rst

+9
Original file line numberDiff line numberDiff line change
@@ -4,6 +4,15 @@ Change Log
44

55
Notable project changes in various releases.
66

7+
1.2
8+
===
9+
10+
Added
11+
-----
12+
13+
* infog2l accepts also an array of indices
14+
15+
716
1.1
817
===
918

CMakeLists.txt

+1-1
Original file line numberDiff line numberDiff line change
@@ -8,7 +8,7 @@ include(ScalapackFxUtils)
88

99
include(${CMAKE_CURRENT_SOURCE_DIR}/config.cmake)
1010

11-
project(ScalapackFx VERSION 1.1.0 LANGUAGES Fortran)
11+
project(ScalapackFx VERSION 1.2.0 LANGUAGES Fortran)
1212

1313
setup_build_type()
1414

doc/doxygen/Doxyfile

+1-1
Original file line numberDiff line numberDiff line change
@@ -32,7 +32,7 @@ PROJECT_NAME = "ScaLAPACKFX"
3232
# This could be handy for archiving the generated documentation or
3333
# if some version control system is used.
3434

35-
PROJECT_NUMBER = "1.1.0"
35+
PROJECT_NUMBER = "1.2.0"
3636

3737
# Using the PROJECT_BRIEF tag one can provide an optional one line description
3838
# for a project that appears at the top of each page and should give viewer

doc/sphinx/conf.py

+2-2
Original file line numberDiff line numberDiff line change
@@ -45,10 +45,10 @@
4545
# built documents.
4646
#
4747
# The short X.Y version.
48-
version = '1.1'
48+
version = '1.2'
4949

5050
# The full version, including alpha/beta/rc tags.
51-
release = '1.1.0'
51+
release = '1.2.0'
5252

5353
# The language for content autogenerated by Sphinx. Refer to documentation
5454
# for a list of supported languages.

lib/scalapackfx.fpp

+92-2
Original file line numberDiff line numberDiff line change
@@ -153,6 +153,11 @@ module scalapackfx_module
153153
module procedure scalafx_creatematrix_complex, scalafx_creatematrix_dcomplex
154154
end interface scalafx_creatematrix
155155

156+
!> Maps global position in a distributed matrix to local one.
157+
interface scalafx_infog2l
158+
module procedure scalafx_infog2l_single, scalafx_infog2l_array
159+
end interface scalafx_infog2l
160+
156161
!************************************************************************
157162
!*** ppotrf
158163
!************************************************************************
@@ -1965,7 +1970,8 @@ contains
19651970
!! \param rsrc Row of the process owning the local matrix.
19661971
!! \param csrc Column of the process owning the local matrix.
19671972
!!
1968-
subroutine scalafx_infog2l(mygrid, desc, grow, gcol, lrow, lcol, rsrc, csrc)
1973+
subroutine scalafx_infog2l_single(mygrid, desc, grow, gcol,&
1974+
& lrow, lcol, rsrc, csrc)
19691975
type(blacsgrid), intent(in) :: mygrid
19701976
integer, intent(in) :: desc(DLEN_)
19711977
integer, intent(in) :: grow, gcol
@@ -1975,8 +1981,92 @@ contains
19751981
call infog2l(grow, gcol, desc, mygrid%nrow, mygrid%ncol, mygrid%myrow,&
19761982
& mygrid%mycol, lrow, lcol, rsrc, csrc)
19771983

1978-
end subroutine scalafx_infog2l
1984+
end subroutine scalafx_infog2l_single
1985+
1986+
!> Maps global positions in a distributed matrix to local one.
1987+
!!
1988+
!! \param mygrid BLACS descriptor.
1989+
!! \param desc Descriptor of the distributed matrix.
1990+
!! \param grow Global row indices.
1991+
!! \param gcol Global column indices.
1992+
!! \param lrow Local row indices on output.
1993+
!! \param lcol Local column indices on output.
1994+
!! \param rsrc Rows of the process owning the local matrix.
1995+
!! \param csrc Columns of the process owning the local matrix.
1996+
!! \param calcAllIndices Whether to calculate all lrow and lcol,
1997+
!! even if the current process does not own them. (default: true)
1998+
!!
1999+
subroutine scalafx_infog2l_array(mygrid, desc, grow, gcol,&
2000+
& lrow, lcol, rsrc, csrc, calcAllIndices)
2001+
type(blacsgrid), intent(in) :: mygrid
2002+
integer, intent(in) :: desc(DLEN_)
2003+
integer, intent(in) :: grow(:), gcol(:)
2004+
integer, intent(out) :: lrow(:), rsrc(:)
2005+
integer, intent(out) :: lcol(:), csrc(:)
2006+
logical, intent(in), optional :: calcAllIndices
2007+
2008+
call scalapackfx_infog2l_helper(grow, desc(MB_), desc(RSRC_),&
2009+
& mygrid%myrow, mygrid%nrow, lrow, rsrc, calcAllIndices)
2010+
2011+
call scalapackfx_infog2l_helper(gcol, desc(NB_), desc(CSRC_),&
2012+
& mygrid%mycol, mygrid%ncol, lcol, csrc, calcAllIndices)
2013+
2014+
end subroutine scalafx_infog2l_array
2015+
2016+
!> Helper routine for scalafx_infog2l_array.
2017+
!!
2018+
!! \param globalInd Global row/column indices.
2019+
!! \param descB Either desc(MB_) or desc(NB_).
2020+
!! \param descSRC Either desc(RSRC_) or desc(CSRC_).
2021+
!! \param myPos Row/column of the current process.
2022+
!! \param nPos Number of rows/columns.
2023+
!! \param localInd Local row/column indices on output.
2024+
!! \param localPos Rows/columns of the process owning the local matrix.
2025+
!! \param calcAllIndices Whether to calculate all local indices,
2026+
!! even if the current process does not own them. (default: true)
2027+
!!
2028+
subroutine scalapackfx_infog2l_helper(globalInd, descB, descSRC,&
2029+
& myPos, nPos, localInd, localPos, calcAllIndices)
2030+
integer, intent(in) :: globalInd(:)
2031+
integer, intent(in) :: descB, descSRC
2032+
integer, intent(in) :: myPos, nPos
2033+
integer, intent(out) :: localInd(:), localPos(:)
2034+
logical, intent(in), optional :: calcAllIndices
2035+
2036+
real(dp) :: inv
2037+
integer, dimension(size(globalInd)) :: blk
2038+
integer :: check, i
2039+
logical :: calcAllIndices_
2040+
2041+
! Note that we explicitly multiply with a double here instead of
2042+
! dividing by an integer to enhance performance.
2043+
inv = 1.0_dp / real(descB, kind=dp)
2044+
blk = (globalInd - 1) * inv
2045+
2046+
check = modulo(myPos - descSRC, nPos)
2047+
2048+
localPos = mod(blk + descSRC, nPos)
2049+
2050+
calcAllIndices_ = .true.
2051+
if (present(calcAllIndices)) then
2052+
calcAllIndices_ = calcAllIndices
2053+
end if
2054+
2055+
do i = 1, size(globalInd)
2056+
if (calcAllIndices_ .or. myPos == localPos(i)) then
2057+
localInd(i) = (blk(i) / nPos + 1) * descB + 1
2058+
if (check >= mod(blk(i), nPos)) then
2059+
if (myPos == localPos(i)) then
2060+
localInd(i) = localInd(i) + mod(globalInd(i) - 1, descB)
2061+
end if
2062+
localInd(i) = localInd(i) - descB
2063+
end if
2064+
else
2065+
localInd(i) = -1
2066+
end if
2067+
end do
19792068

2069+
end subroutine scalapackfx_infog2l_helper
19802070

19812071
!> Maps local row or column index onto global matrix position.
19822072
!!

lib/scalapackfx_tools.fpp

+54-17
Original file line numberDiff line numberDiff line change
@@ -68,15 +68,33 @@
6868
integer, intent(in) :: ii, jj
6969
${FTYPE}$, intent(inout) :: glob(:,:)
7070

71-
integer :: i2, j2, iloc, jloc, prow, pcol
71+
integer :: i2, j2, nr, nc
72+
integer, dimension(size(loc, dim=1)) :: irows, iloc, prow
73+
integer, dimension(size(loc, dim=2)) :: icols, jloc, pcol
74+
75+
nr = size(loc, dim=1)
76+
nc = size(loc, dim=2)
77+
78+
do i2 = 1, nr
79+
irows(i2) = i2 + ii - 1
80+
end do
81+
82+
do j2 = 1, nc
83+
icols(j2) = j2 + jj - 1
84+
end do
85+
86+
call scalafx_infog2l(mygrid, desc, irows, icols, iloc, jloc,&
87+
& prow, pcol, .false.)
7288

73-
do j2 = 1, size(loc, dim=2)
74-
do i2 = 1, size(loc, dim=1)
75-
call scalafx_infog2l(mygrid, desc, i2 + ii - 1, j2 + jj - 1, &
76-
& iloc, jloc, prow, pcol)
77-
if (prow == mygrid%myrow .and. pcol == mygrid%mycol) then
78-
glob(iloc, jloc) = glob(iloc, jloc) + loc(i2, j2)
89+
do j2 = 1, nc
90+
if (pcol(j2) /= mygrid%mycol) then
91+
cycle
92+
end if
93+
do i2 = 1, nr
94+
if (prow(i2) /= mygrid%myrow) then
95+
cycle
7996
end if
97+
glob(iloc(i2), jloc(j2)) = glob(iloc(i2), jloc(j2)) + loc(i2, j2)
8098
end do
8199
end do
82100

@@ -109,17 +127,36 @@
109127
${FTYPE}$, intent(in) :: glob(:,:)
110128
${FTYPE}$, intent(out) :: loc(:,:)
111129

112-
integer :: i2, j2, iloc, jloc, prow, pcol
130+
integer :: i2, j2, nr, nc
131+
integer, dimension(size(loc, dim=1)) :: irows, iloc, prow
132+
integer, dimension(size(loc, dim=2)) :: icols, jloc, pcol
133+
134+
nr = size(loc, dim=1)
135+
nc = size(loc, dim=2)
136+
137+
do i2 = 1, nr
138+
irows(i2) = i2 + ii - 1
139+
end do
140+
141+
do j2 = 1, nc
142+
icols(j2) = j2 + jj - 1
143+
end do
144+
145+
call scalafx_infog2l(mygrid, desc, irows, icols, iloc, jloc,&
146+
& prow, pcol, .false.)
113147

114-
loc(:,:) = 0.0_dp
115-
do j2 = 1, size(loc, dim=2)
116-
do i2 = 1, size(loc, dim=1)
117-
call scalafx_infog2l(mygrid, desc, i2 + ii - 1, j2 + jj - 1, &
118-
& iloc, jloc, prow, pcol)
119-
if (prow == mygrid%myrow .and. pcol == mygrid%mycol) then
120-
loc(i2, j2) = glob(iloc, jloc)
121-
end if
122-
end do
148+
do j2 = 1, nc
149+
if (pcol(j2) == mygrid%mycol) then
150+
do i2 = 1, nr
151+
if (prow(i2) == mygrid%myrow) then
152+
loc(i2, j2) = glob(iloc(i2), jloc(j2))
153+
else
154+
loc(i2, j2) = 0.0_dp
155+
end if
156+
end do
157+
else
158+
loc(:, j2) = 0.0_dp
159+
end if
123160
end do
124161

125162
end subroutine cpg2l_${SUFFIX}$

test/CMakeLists.txt

+1
Original file line numberDiff line numberDiff line change
@@ -3,6 +3,7 @@ set(targets
33
test_subgrids)
44

55
set(common-dep-targets
6+
test_cpg2l
67
test_det
78
test_diag
89
test_gemr2d

test/test_cpg2l.f90

+106
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,106 @@
1+
!> Testing rank one updates.
2+
program test_cpg2l
3+
use, intrinsic :: iso_fortran_env, stdout => output_unit
4+
use test_common_module
5+
use libscalapackfx_module
6+
implicit none
7+
8+
9+
! Block size (using an extremely small value for test purposes)
10+
integer, parameter :: bsize = 2
11+
12+
call main()
13+
14+
contains
15+
16+
subroutine main()
17+
type(blacsgrid) :: grid1, grid2
18+
19+
integer :: nprow, npcol, iproc, nproc
20+
21+
! Initialize blas and create a square processor grid
22+
call blacsfx_pinfo(iproc, nproc)
23+
do nprow = int(sqrt(real(nproc, dp))), nproc
24+
if (mod(nproc, nprow) == 0) then
25+
exit
26+
end if
27+
end do
28+
npcol = nproc / nprow
29+
30+
call grid1%initgrid(nprow, npcol)
31+
if (grid1%lead) then
32+
write(stdout, "(A,2(1X,I0))") "# processor grid:", nprow, npcol
33+
end if
34+
35+
call grid2%initgrid(1, nproc)
36+
if (grid2%lead) then
37+
write(stdout, "(A,2(1X,I0))") "# processor grid:", 1, nproc
38+
end if
39+
40+
if (.not. readMatrixAndTest(grid1, 2, 2, 1, 2)) then
41+
write(stdout, "(A)") "Test 1 failed"
42+
end if
43+
if (.not. readMatrixAndTest(grid1, 5, 5, 1, 1)) then
44+
write(stdout, "(A)") "Test 2 failed"
45+
end if
46+
if (.not. readMatrixAndTest(grid2, 2, 2, 1, 2)) then
47+
write(stdout, "(A)") "Test 3 failed"
48+
end if
49+
if (.not. readMatrixAndTest(grid2, 3, 5, 3, 1)) then
50+
write(stdout, "(A)") "Test 4 failed"
51+
end if
52+
53+
call grid1%destruct()
54+
call grid1%initgrid(nproc, 1)
55+
if (.not. readMatrixAndTest(grid1, 2, 2, 1, 2)) then
56+
write(stdout, "(A)") "Test 5 failed"
57+
end if
58+
59+
! Finish blacs.
60+
call blacsfx_exit()
61+
62+
end subroutine main
63+
64+
function readMatrixAndTest(mygrid, iSize, jSize, i0, j0) result(success)
65+
type(blacsgrid), intent(inout) :: mygrid
66+
integer, intent(in) :: iSize, jSize, i0, j0
67+
logical :: success
68+
69+
real(dp), allocatable :: glob(:,:), localTest(:,:), localRef(:,:)
70+
integer :: desc(DLEN_)
71+
integer :: mm, nn, i, j
72+
integer :: iloc, jloc, prow, pcol
73+
74+
! Read in matrix from disc.
75+
call readfromfile(mygrid, "hamsqr1.dat", bsize, bsize, glob, desc)
76+
mm = desc(M_)
77+
nn = desc(N_)
78+
if (mygrid%lead) then
79+
write(stdout, "(A,2(1X,I0))") "# global matrix size:", mm, nn
80+
write(stdout, "(A,2(1X,I0))") "# local matrix size on leader:",&
81+
& size(glob, dim=1), size(glob, dim=2)
82+
end if
83+
84+
allocate(localRef(iSize,jSize), localTest(iSize,jSize))
85+
86+
localRef(:,:) = 0.0_dp
87+
do j = 1, jSize
88+
do i = 1, iSize
89+
call scalafx_infog2l(mygrid, desc, i + i0 - 1, j + j0 - 1, iloc, jloc,&
90+
& prow, pcol)
91+
if (prow == mygrid%myrow .and. pcol == mygrid%mycol) then
92+
localRef(i, j) = glob(iloc, jloc)
93+
end if
94+
end do
95+
end do
96+
97+
localTest(:,:) = 0.0_dp
98+
call scalafx_cpg2l(mygrid, desc, i0, j0, glob, localTest)
99+
100+
success = all(localTest == localRef)
101+
102+
end function readMatrixAndTest
103+
104+
105+
end program test_cpg2l
106+

0 commit comments

Comments
 (0)