Skip to content

Commit

Permalink
Rename cp_context_type to reflect the reference to the blacs library
Browse files Browse the repository at this point in the history
  • Loading branch information
Frederick Stein authored and fstein93 committed Feb 28, 2023
1 parent 4f41ba7 commit cfb00a7
Show file tree
Hide file tree
Showing 4 changed files with 26 additions and 27 deletions.
5 changes: 2 additions & 3 deletions src/fm/cp_blacs_env.F
Original file line number Diff line number Diff line change
Expand Up @@ -14,7 +14,7 @@
! **************************************************************************************************
MODULE cp_blacs_env
USE cp_array_utils, ONLY: cp_2d_i_write
USE cp_context_types, ONLY: cp_context_type
USE cp_blacs_types, ONLY: cp_blacs_type
USE cp_para_env, ONLY: cp_para_env_release
USE cp_para_types, ONLY: cp_para_env_type
USE kinds, ONLY: dp
Expand Down Expand Up @@ -53,7 +53,7 @@ MODULE cp_blacs_env
!> 08.2002 created [fawzi]
!> \author Fawzi Mohamed
! **************************************************************************************************
TYPE, EXTENDS(cp_context_type) :: cp_blacs_env_type
TYPE, EXTENDS(cp_blacs_type) :: cp_blacs_env_type
INTEGER, DIMENSION(2) :: mepos = -1, num_pe = -1
INTEGER :: my_pid = -1, n_pid = -1, ref_count = -1
TYPE(cp_para_env_type), POINTER :: para_env => NULL()
Expand Down Expand Up @@ -212,7 +212,6 @@ SUBROUTINE cp_blacs_env_create_low(blacs_env, para_env, blacs_grid_layout, blacs
END SELECT
END IF

! blacs_env will be set to the blacs context for this blacs env, this is not the same as the MPI context
my_row_major = .TRUE.
IF (PRESENT(row_major)) my_row_major = row_major
IF (my_row_major) THEN
Expand Down
32 changes: 16 additions & 16 deletions src/fm/cp_context_types.F → src/fm/cp_blacs_types.F
Original file line number Diff line number Diff line change
Expand Up @@ -15,19 +15,19 @@
!> 12.2003 created [Joost]
!> \author Joost VandeVondele
! **************************************************************************************************
MODULE cp_context_types
MODULE cp_blacs_types

USE kinds, ONLY: dp
USE message_passing, ONLY: mp_comm_type
#include "../base/base_uses.f90"

IMPLICIT NONE
CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'cp_context_types'
CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'cp_blacs_types'
PRIVATE

PUBLIC :: cp_context_type
PUBLIC :: cp_blacs_type

TYPE cp_context_type
TYPE cp_blacs_type
PRIVATE
#if defined(__SCALAPACK)
INTEGER :: context_handle = -1
Expand Down Expand Up @@ -62,7 +62,7 @@ MODULE cp_context_types
!> \param npcol ...
! **************************************************************************************************
SUBROUTINE cp_blacs_gridinit(this, comm, order, nprow, npcol)
CLASS(cp_context_type), INTENT(OUT) :: this
CLASS(cp_blacs_type), INTENT(OUT) :: this
CLASS(mp_comm_type), INTENT(IN) :: comm
CHARACTER(len=1), INTENT(IN):: order
INTEGER, INTENT(IN) :: nprow, npcol
Expand All @@ -85,7 +85,7 @@ END SUBROUTINE cp_blacs_gridinit
!> \param this ...
! **************************************************************************************************
SUBROUTINE cp_blacs_gridexit(this)
CLASS(cp_context_type), INTENT(IN) :: this
CLASS(cp_blacs_type), INTENT(IN) :: this
#if defined(__SCALAPACK)
CALL blacs_gridexit(this%context_handle)
#else
Expand All @@ -102,7 +102,7 @@ END SUBROUTINE cp_blacs_gridexit
!> \param mypcol ...
! **************************************************************************************************
SUBROUTINE cp_blacs_gridinfo(this, nprow, npcol, myprow, mypcol)
CLASS(cp_context_type), INTENT(IN) :: this
CLASS(cp_blacs_type), INTENT(IN) :: this
INTEGER, INTENT(OUT) :: nprow, npcol, myprow, mypcol
#if defined(__SCALAPACK)
CALL blacs_gridinfo(this%context_handle, nprow, npcol, myprow, mypcol)
Expand All @@ -129,7 +129,7 @@ END SUBROUTINE cp_blacs_gridinfo
!> \param val ...
! **************************************************************************************************
SUBROUTINE cp_blacs_set(this, what, val)
CLASS(cp_context_type), INTENT(IN) :: this
CLASS(cp_blacs_type), INTENT(IN) :: this
INTEGER, INTENT(IN) :: what, val
#if defined(__SCALAPACK)
CALL blacs_set(this%context_handle, what, val)
Expand All @@ -151,7 +151,7 @@ END SUBROUTINE cp_blacs_set
!> \param LDA ...
! **************************************************************************************************
SUBROUTINE cp_blacs_zgebs2d(this, SCOPE, TOP, M, N, A, LDA)
CLASS(cp_context_type), INTENT(IN) :: this
CLASS(cp_blacs_type), INTENT(IN) :: this
CHARACTER(len=1), INTENT(IN) :: SCOPE, TOP
INTEGER, INTENT(IN) :: M, N, LDA
COMPLEX(KIND=dp) :: A
Expand Down Expand Up @@ -180,7 +180,7 @@ SUBROUTINE cp_blacs_zgebs2d(this, SCOPE, TOP, M, N, A, LDA)
!> \param CSRC ...
! **************************************************************************************************
SUBROUTINE cp_blacs_zgebr2d(this, SCOPE, TOP, M, N, A, LDA, RSRC, CSRC)
CLASS(cp_context_type), INTENT(IN) :: this
CLASS(cp_blacs_type), INTENT(IN) :: this
CHARACTER(len=1), INTENT(IN) :: SCOPE, TOP
INTEGER, INTENT(IN) :: M, N, LDA
INTEGER, INTENT(IN) :: RSRC, CSRC
Expand Down Expand Up @@ -211,7 +211,7 @@ SUBROUTINE cp_blacs_zgebr2d(this, SCOPE, TOP, M, N, A, LDA, RSRC, CSRC)
!> \param LDA ...
! **************************************************************************************************
SUBROUTINE cp_blacs_dgebs2d(this, SCOPE, TOP, M, N, A, LDA)
CLASS(cp_context_type), INTENT(IN) :: this
CLASS(cp_blacs_type), INTENT(IN) :: this
CHARACTER(len=1), INTENT(IN) :: SCOPE, TOP
INTEGER, INTENT(IN) :: M, N, LDA
REAL(KIND=dp) :: A
Expand Down Expand Up @@ -240,7 +240,7 @@ SUBROUTINE cp_blacs_dgebs2d(this, SCOPE, TOP, M, N, A, LDA)
!> \param CSRC ...
! **************************************************************************************************
SUBROUTINE cp_blacs_dgebr2d(this, SCOPE, TOP, M, N, A, LDA, RSRC, CSRC)
CLASS(cp_context_type), INTENT(IN) :: this
CLASS(cp_blacs_type), INTENT(IN) :: this
CHARACTER(len=1), INTENT(IN) :: SCOPE, TOP
INTEGER, INTENT(IN) :: M, N, LDA
INTEGER, INTENT(IN) :: RSRC, CSRC
Expand All @@ -266,7 +266,7 @@ SUBROUTINE cp_blacs_dgebr2d(this, SCOPE, TOP, M, N, A, LDA, RSRC, CSRC)
!> \return ...
! **************************************************************************************************
ELEMENTAL INTEGER FUNCTION cp_blacs_get_handle(this)
CLASS(cp_context_type), INTENT(IN) :: this
CLASS(cp_blacs_type), INTENT(IN) :: this
#if defined(__SCALAPACK)
cp_blacs_get_handle = this%context_handle
#else
Expand All @@ -282,7 +282,7 @@ ELEMENTAL INTEGER FUNCTION cp_blacs_get_handle(this)
!> \return ...
! **************************************************************************************************
ELEMENTAL LOGICAL FUNCTION cp_context_is_equal(this, other)
CLASS(cp_context_type), INTENT(IN) :: this, other
CLASS(cp_blacs_type), INTENT(IN) :: this, other
#if defined(__SCALAPACK)
cp_context_is_equal = (this%context_handle == other%context_handle)
#else
Expand All @@ -299,7 +299,7 @@ END FUNCTION cp_context_is_equal
!> \return ...
! **************************************************************************************************
ELEMENTAL LOGICAL FUNCTION cp_context_is_not_equal(this, other)
CLASS(cp_context_type), INTENT(IN) :: this, other
CLASS(cp_blacs_type), INTENT(IN) :: this, other
#if defined(__SCALAPACK)
cp_context_is_not_equal = (this%context_handle /= other%context_handle)
#else
Expand All @@ -309,4 +309,4 @@ ELEMENTAL LOGICAL FUNCTION cp_context_is_not_equal(this, other)
#endif
END FUNCTION cp_context_is_not_equal

END MODULE cp_context_types
END MODULE cp_blacs_types
4 changes: 2 additions & 2 deletions src/fm/cp_fm_diag.F
Original file line number Diff line number Diff line change
Expand Up @@ -16,7 +16,7 @@
! **************************************************************************************************
MODULE cp_fm_diag

USE cp_context_types, ONLY: cp_context_type
USE cp_blacs_types, ONLY: cp_blacs_type
USE cp_blacs_env, ONLY: cp_blacs_env_type
USE cp_fm_basic_linalg, ONLY: cp_fm_column_scale, &
cp_fm_gemm, &
Expand Down Expand Up @@ -1043,7 +1043,7 @@ SUBROUTINE cp_fm_block_jacobi(matrix, eigenvectors, eigval, thresh, &
INTEGER, DIMENSION(9) :: desca, descz, desc_a_block, &
desc_ev_loc
TYPE(mp_comm_type):: allgrp
TYPE(cp_context_type) :: ictxt_loc
TYPE(cp_blacs_type) :: ictxt_loc
INTEGER, EXTERNAL :: numroc, indxl2g, indxg2l
#endif

Expand Down
12 changes: 6 additions & 6 deletions src/fm/cp_fm_types.F
Original file line number Diff line number Diff line change
Expand Up @@ -14,7 +14,7 @@
! **************************************************************************************************
MODULE cp_fm_types
USE cp_blacs_env, ONLY: cp_blacs_env_type
USE cp_context_types, ONLY: cp_context_type
USE cp_blacs_types, ONLY: cp_blacs_type
USE cp_fm_struct, ONLY: cp_fm_struct_equivalent,&
cp_fm_struct_get,&
cp_fm_struct_release,&
Expand Down Expand Up @@ -1803,7 +1803,7 @@ SUBROUTINE cp_fm_to_fm_submat_general(source, &
INTEGER, INTENT(IN) :: nrows, ncols, s_firstrow, s_firstcol, &
d_firstrow, d_firstcol
CLASS(cp_context_type), INTENT(IN) :: global_context
CLASS(cp_blacs_type), INTENT(IN) :: global_context
CHARACTER(LEN=*), PARAMETER :: routineN = 'cp_fm_to_fm_submat_general'
Expand Down Expand Up @@ -1959,7 +1959,7 @@ SUBROUTINE cp_fm_write_unformatted(fm, unit)
INTEGER, DIMENSION(9) :: desc
REAL(KIND=dp), DIMENSION(:), POINTER :: vecbuf
REAL(KIND=dp), DIMENSION(:, :), POINTER :: newdat
TYPE(cp_context_type) :: ictxt_loc
TYPE(cp_blacs_type) :: ictxt_loc
INTEGER, EXTERNAL :: numroc
#endif
Expand All @@ -1975,7 +1975,7 @@ SUBROUTINE cp_fm_write_unformatted(fm, unit)
! get a new context
CALL ictxt_loc%gridinit(para_env, 'R', 1, num_pe)
CALL ictxt_loc%gridinfo(nprow, npcol, myprow, mypcol)
CALL descinit(desc, nrow_global, ncol_global, rb, max_block, 0, 0, ictxt_loc, nrow_global, info)
CALL descinit(desc, nrow_global, ncol_global, rb, max_block, 0, 0, ictxt_loc%get_handle(), nrow_global, info)
CPASSERT(info == 0)
in = numroc(ncol_global, max_block, mypcol, 0, npcol)
Expand Down Expand Up @@ -2065,7 +2065,7 @@ SUBROUTINE cp_fm_write_formatted(fm, unit, header, value_format)
INTEGER, DIMENSION(9) :: desc
REAL(KIND=dp), DIMENSION(:), POINTER :: vecbuf
REAL(KIND=dp), DIMENSION(:, :), POINTER :: newdat
TYPE(cp_context_type) :: ictxt_loc
TYPE(cp_blacs_type) :: ictxt_loc
INTEGER, EXTERNAL :: numroc
#endif
Expand Down Expand Up @@ -2093,7 +2093,7 @@ SUBROUTINE cp_fm_write_formatted(fm, unit, header, value_format)
! get a new context
CALL ictxt_loc%gridinit(para_env, 'R', 1, num_pe)
CALL ictxt_loc%gridinfo(nprow, npcol, myprow, mypcol)
CALL descinit(desc, nrow_global, ncol_global, rb, max_block, 0, 0, ictxt_loc, nrow_global, info)
CALL descinit(desc, nrow_global, ncol_global, rb, max_block, 0, 0, ictxt_loc%get_handle(), nrow_global, info)
CPASSERT(info == 0)
in = numroc(ncol_global, max_block, mypcol, 0, npcol)
Expand Down

0 comments on commit cfb00a7

Please sign in to comment.