Skip to content

Commit

Permalink
(implicit ps) switch on/off more debug options from input file.
Browse files Browse the repository at this point in the history
svn-origin-rev: 15267
  • Loading branch information
seyedb committed Apr 28, 2015
1 parent 820ef3b commit e2f0567
Show file tree
Hide file tree
Showing 2 changed files with 45 additions and 21 deletions.
3 changes: 2 additions & 1 deletion src/input_cp2k_poisson.F
Expand Up @@ -792,7 +792,8 @@ SUBROUTINE create_dbc_section(section,error)

CALL keyword_create(keyword, name="DEBUG", &
description="Whether or not to print out the values of the electrostatic potential "// &
"at Dirichlet regions.", &
"at Dirichlet regions, as well as the coordinates of the vertices of the region and "// &
"its tessellation.", &
usage="DEBUG <logical>", default_l_val=.FALSE., error=error)
CALL section_add_keyword(section, keyword, error=error)
CALL keyword_release(keyword, error=error)
Expand Down
63 changes: 43 additions & 20 deletions src/pw/dirichlet_bc_methods.F
Expand Up @@ -46,7 +46,6 @@ MODULE dirichlet_bc_methods
IMPLICIT NONE
PRIVATE
CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'dirichlet_bc_methods'
LOGICAL, PRIVATE, PARAMETER :: debug = .FALSE.

PUBLIC dirichlet_boundary_region_setup

Expand Down Expand Up @@ -81,7 +80,7 @@ SUBROUTINE dirichlet_boundary_region_setup(pw_pool, poisson_params, dbcs, error)
n_aa_cuboidal, n_aa_planar, n_dbcs, n_planar, n_xaa_cylindrical, unit_nr
INTEGER, DIMENSION(3) :: n_prtn
INTEGER, DIMENSION(:), POINTER :: xaa_cylindrical_nsides
LOGICAL :: smooth
LOGICAL :: debug, smooth
REAL(dp) :: base_radius, v_D, zeta
REAL(dp), ALLOCATABLE, DIMENSION(:) :: x_glbl, x_locl, y_glbl, &
y_locl, z_glbl, z_locl
Expand All @@ -98,6 +97,8 @@ SUBROUTINE dirichlet_boundary_region_setup(pw_pool, poisson_params, dbcs, error)
unit_nr = -1
ENDIF

debug = poisson_params%dbc_params%debug

n_aa_planar = poisson_params%dbc_params%n_aa_planar
n_aa_cuboidal = poisson_params%dbc_params%n_aa_cuboidal
n_planar = poisson_params%dbc_params%n_planar
Expand All @@ -117,7 +118,7 @@ SUBROUTINE dirichlet_boundary_region_setup(pw_pool, poisson_params, dbcs, error)
ALLOCATE(dbcs(n_dbcs))
IF (unit_nr .GT. 0) THEN
WRITE(unit_nr,'(/,T3,A,A,/,T3,A)') "POISSON| IMPLICIT (GENERALIZED) SOLVER ", REPEAT('-', 39), &
"POISSON| Preparing Dirichlet boundary regions ..."
"POISSON| Preparing Dirichlet regions ..."
END IF

DO j = 1, n_aa_planar
Expand All @@ -129,18 +130,19 @@ SUBROUTINE dirichlet_boundary_region_setup(pw_pool, poisson_params, dbcs, error)
zeta = poisson_params%dbc_params%aa_planar_zeta(j)

IF (unit_nr .GT. 0) THEN
WRITE(unit_nr,'(T3,A,I5)') "POISSON| DBC", j
WRITE(unit_nr,'(T3,A,I5)') "POISSON| Dirichlet region", j
WRITE(unit_nr,'(T3,A)') "POISSON| type : AXIS-ALIGNED PLANAR"
WRITE(unit_nr,'(T3,A,E13.4,2X,A)') "POISSON| applied potential :", v_D, "[Eh/e]"
END IF
CALL create_aa_planar_dbc(x_glbl, y_glbl, z_glbl, &
poisson_params%dbc_params%aa_planar_xxtnt(:,j), &
poisson_params%dbc_params%aa_planar_yxtnt(:,j), &
poisson_params%dbc_params%aa_planar_zxtnt(:,j), &
v_D, smooth, zeta, dbc_id, dbcs(j)%dirichlet_bc, error)
v_D, smooth, zeta, dbc_id, dbcs(j)%dirichlet_bc, &
debug, error)

CALL dirichlet_bc_partition(v_D, smooth, zeta, n_prtn, pw_pool, x_glbl, y_glbl, z_glbl, &
x_locl, y_locl, z_locl, dbcs(j)%dirichlet_bc, error)
x_locl, y_locl, z_locl, dbcs(j)%dirichlet_bc, debug, error)
END DO

l = n_aa_planar
Expand All @@ -153,18 +155,19 @@ SUBROUTINE dirichlet_boundary_region_setup(pw_pool, poisson_params, dbcs, error)
zeta = poisson_params%dbc_params%aa_cuboidal_zeta(j - l)

IF (unit_nr .GT. 0) THEN
WRITE(unit_nr,'(T3,A,I5)') "POISSON| DBC", j
WRITE(unit_nr,'(T3,A,I5)') "POISSON| Dirichlet region", j
WRITE(unit_nr,'(T3,A)') "POISSON| type : AXIS-ALIGNED CUBOIDAL"
WRITE(unit_nr,'(T3,A,E13.4,2X,A)') "POISSON| applied potential :", v_D, "[Eh/e]"
END IF
CALL create_aa_cuboidal_dbc(x_glbl, y_glbl, z_glbl, &
poisson_params%dbc_params%aa_cuboidal_xxtnt(:,j - l), &
poisson_params%dbc_params%aa_cuboidal_yxtnt(:,j - l), &
poisson_params%dbc_params%aa_cuboidal_zxtnt(:,j - l), &
v_D, smooth, zeta, dbc_id, dbcs(j)%dirichlet_bc, error)
v_D, smooth, zeta, dbc_id, dbcs(j)%dirichlet_bc, &
debug, error)

CALL dirichlet_bc_partition(v_D, smooth, zeta, n_prtn, pw_pool, x_glbl, y_glbl, z_glbl, &
x_locl, y_locl, z_locl, dbcs(j)%dirichlet_bc, error)
x_locl, y_locl, z_locl, dbcs(j)%dirichlet_bc, debug, error)
END DO

l = n_aa_planar + n_aa_cuboidal
Expand All @@ -177,18 +180,19 @@ SUBROUTINE dirichlet_boundary_region_setup(pw_pool, poisson_params, dbcs, error)
zeta = poisson_params%dbc_params%planar_zeta(j - l)

IF (unit_nr .GT. 0) THEN
WRITE(unit_nr,'(T3,A,I5)') "POISSON| DBC", j
WRITE(unit_nr,'(T3,A,I5)') "POISSON| Dirichlet region", j
WRITE(unit_nr,'(T3,A)') "POISSON| type : PLANAR"
WRITE(unit_nr,'(T3,A,E13.4,2X,A)') "POISSON| applied potential :", v_D, "[Eh/e]"
END IF
CALL create_arbitrary_planar_dbc(x_glbl, y_glbl, z_glbl, &
poisson_params%dbc_params%planar_Avtx(:,j - l), &
poisson_params%dbc_params%planar_Bvtx(:,j - l), &
poisson_params%dbc_params%planar_Cvtx(:,j - l), &
v_D, smooth, zeta, dbc_id, dbcs(j)%dirichlet_bc, error)
v_D, smooth, zeta, dbc_id, dbcs(j)%dirichlet_bc, &
debug, error)

CALL dirichlet_bc_partition(v_D, smooth, zeta, n_prtn, pw_pool, x_glbl, y_glbl, z_glbl, &
x_locl, y_locl, z_locl, dbcs(j)%dirichlet_bc, error)
x_locl, y_locl, z_locl, dbcs(j)%dirichlet_bc, debug, error)
END DO

l = n_aa_planar + n_aa_cuboidal + n_planar
Expand All @@ -205,15 +209,15 @@ SUBROUTINE dirichlet_boundary_region_setup(pw_pool, poisson_params, dbcs, error)
apx_type = poisson_params%dbc_params%xaa_cylindrical_apxtyp(j)

IF (unit_nr .GT. 0) THEN
WRITE(unit_nr,'(T3,A,I5)') "POISSON| DBC", l + j
WRITE(unit_nr,'(T3,A,I5)') "POISSON| Dirichlet region", l + j
WRITE(unit_nr,'(T3,A)') "POISSON| type : X-AXIS-ALIGNED CYLINDRICAL"
WRITE(unit_nr,'(T3,A,E13.4,2X,A)') "POISSON| applied potential :", v_D, "[Eh/e]"
END IF
CALL create_xaa_cylindrical_dbc(pw_pool, x_glbl, y_glbl, z_glbl, &
x_locl, y_locl, z_locl, &
poisson_params%dbc_params%xaa_cylindrical_xxtnt(:,j), &
base_center, base_radius, v_D, smooth, zeta, n_prtn, &
dbcs(ind_start : ind_end), apx_type, error)
dbcs(ind_start : ind_end), apx_type, debug, error)

l = l + xaa_cylindrical_nsides(j)
END DO
Expand Down Expand Up @@ -244,14 +248,15 @@ END SUBROUTINE dirichlet_boundary_region_setup
!> \param y_locl y grid vetor of the simulation box local to this process
!> \param z_locl z grid vetor of the simulation box local to this process
!> \param dirichlet_bc the dirichlet_bc object to be partitioned
!> \param debug whether or not to print out the coordinates of the vertices
!> \param error cp2k error
!>
!> \par History
!> 10.2014 created [Hossein Bani-Hashemian]
!> \author Mohammad Hossein Bani-Hashemian
! *****************************************************************************
SUBROUTINE dirichlet_bc_partition(v_D, smooth, zeta, n_prtn, pw_pool, x_glbl, y_glbl, z_glbl, &
x_locl, y_locl, z_locl, dirichlet_bc, error)
x_locl, y_locl, z_locl, dirichlet_bc, debug, error)

REAL(dp), INTENT(IN) :: v_D
LOGICAL, INTENT(IN) :: smooth
Expand All @@ -263,6 +268,7 @@ SUBROUTINE dirichlet_bc_partition(v_D, smooth, zeta, n_prtn, pw_pool, x_glbl, y_
x_locl, y_locl, z_locl
TYPE(dirichlet_bc_type), INTENT(INOUT), &
POINTER :: dirichlet_bc
LOGICAL, INTENT(IN) :: debug
TYPE(cp_error_type), INTENT(INOUT) :: error

CHARACTER(LEN=*), PARAMETER :: routineN = 'dirichlet_bc_partition', &
Expand Down Expand Up @@ -337,6 +343,8 @@ SUBROUTINE dirichlet_bc_partition(v_D, smooth, zeta, n_prtn, pw_pool, x_glbl, y_
dirichlet_bc%tiles(k)%tile%npts = tile_npts
END DO

IF ((unit_nr .GT. 0) .AND. debug) WRITE(unit_nr, '(T3,A)') REPEAT('=', 78)

DO k = 1, n_tiles
CALL cs_rectangle_release(tiles(k)%tile%rectangle, error)
DEALLOCATE(tiles(k)%tile)
Expand Down Expand Up @@ -370,6 +378,7 @@ SUBROUTINE dirichlet_bc_partition(v_D, smooth, zeta, n_prtn, pw_pool, x_glbl, y_
WRITE(unit_nr,'(T10,A,I1,3F10.3)') &
" vertex ", i, angstrom * dirichlet_bc%box%vertices(:,i)
END DO
WRITE(unit_nr, '(T3,A)') REPEAT('=', 78)
END IF

CALL voxelize_aa_cuboid(dirichlet_bc%tiles(k)%tile%box, x_locl, y_locl, z_locl, &
Expand All @@ -379,6 +388,8 @@ SUBROUTINE dirichlet_bc_partition(v_D, smooth, zeta, n_prtn, pw_pool, x_glbl, y_
dirichlet_bc%tiles(k)%tile%npts = tile_npts
END DO

IF ((unit_nr .GT. 0) .AND. debug) WRITE(unit_nr, '(T3,A)') REPEAT('=', 78)

DEALLOCATE(tiles)

END SELECT
Expand Down Expand Up @@ -413,6 +424,7 @@ END SUBROUTINE dirichlet_bc_partition
!> z interval (defining the region) should be partitioned into
!> \param dbcs the x-axis-aligned cylindrical gate region to be created
!> \param apx_type the type of the n-gonal prism approximating the cylinder
!> \param debug whether or not to print out the coordinates of the vertices
!> \param error cp2k error
!> \par History
!> 08.2014 created [Hossein Bani-Hashemian]
Expand All @@ -421,7 +433,7 @@ END SUBROUTINE dirichlet_bc_partition
SUBROUTINE create_xaa_cylindrical_dbc(pw_pool, &
x_glbl, y_glbl, z_glbl, x_locl, y_locl, z_locl, &
x_xtnt, base_center, base_radius, v_D, smooth, zeta, &
n_prtn, dbcs, apx_type, error)
n_prtn, dbcs, apx_type, debug, error)

TYPE(pw_pool_type), POINTER :: pw_pool
REAL(dp), ALLOCATABLE, DIMENSION(:), &
Expand All @@ -435,6 +447,7 @@ SUBROUTINE create_xaa_cylindrical_dbc(pw_pool, &
TYPE(dirichlet_bc_p_type), &
DIMENSION(:), INTENT(INOUT) :: dbcs
INTEGER, INTENT(IN), OPTIONAL :: apx_type
LOGICAL, INTENT(IN) :: debug
TYPE(cp_error_type), INTENT(INOUT) :: error

CHARACTER(LEN=*), PARAMETER :: routineN = 'create_xaa_cylindrical_dbc', &
Expand Down Expand Up @@ -545,6 +558,7 @@ SUBROUTINE create_xaa_cylindrical_dbc(pw_pool, &
dbcs(j)%dirichlet_bc%n_tiles = 1

IF ((unit_nr .GT. 0) .AND. debug) THEN
WRITE(unit_nr, '(T3,A,A)') "======== debug ", REPEAT('=', 63)
WRITE(unit_nr,'(T7,A,I5,T20,A,I5,A)') "edge", j, "of the", n_dbcs, &
"-gonal prism approximating the cylinder"
DO i = 1, 4
Expand All @@ -554,7 +568,7 @@ SUBROUTINE create_xaa_cylindrical_dbc(pw_pool, &
END IF

CALL dirichlet_bc_partition(v_D, smooth, zeta, n_prtn, pw_pool, x_glbl, y_glbl, z_glbl, &
x_locl, y_locl, z_locl, dbcs(j)%dirichlet_bc, error)
x_locl, y_locl, z_locl, dbcs(j)%dirichlet_bc, debug, error)
END DO

CALL timestop(handle)
Expand All @@ -574,13 +588,14 @@ END SUBROUTINE create_xaa_cylindrical_dbc
!> \param zeta the mollifier's width
!> \param dbc_id unique ID for the planar Dirichlet region
!> \param dirichlet_bc the dirichlet_bc object to be created
!> \param debug whether or not to print out the coordinates of the vertices
!> \param error cp2k error
!> \par History
!> 08.2014 created [Hossein Bani-Hashemian]
!> \author Mohammad Hossein Bani-Hashemian
! *****************************************************************************
SUBROUTINE create_aa_planar_dbc(x_glbl, y_glbl, z_glbl, x_xtnt, y_xtnt, z_xtnt, &
v_D, smooth, zeta, dbc_id, dirichlet_bc, error)
v_D, smooth, zeta, dbc_id, dirichlet_bc, debug, error)
REAL(dp), ALLOCATABLE, DIMENSION(:), &
INTENT(IN) :: x_glbl, y_glbl, z_glbl
Expand All @@ -591,6 +606,7 @@ SUBROUTINE create_aa_planar_dbc(x_glbl, y_glbl, z_glbl, x_xtnt, y_xtnt, z_xtnt,
INTEGER, INTENT(IN) :: dbc_id
TYPE(dirichlet_bc_type), INTENT(INOUT), &
POINTER :: dirichlet_bc
LOGICAL, INTENT(IN) :: debug
TYPE(cp_error_type), INTENT(INOUT) :: error
CHARACTER(LEN=*), PARAMETER :: routineN = 'create_aa_planar_dbc', &
Expand Down Expand Up @@ -685,6 +701,7 @@ SUBROUTINE create_aa_planar_dbc(x_glbl, y_glbl, z_glbl, x_xtnt, y_xtnt, z_xtnt,
END IF
IF ((unit_nr .GT. 0) .AND. debug) THEN
WRITE(unit_nr, '(T3,A,A)') "======== debug ", REPEAT('=', 63)
DO i = 1, 4
WRITE(unit_nr,'(T10,A,I1,3F10.3)') " vertex ", i, &
angstrom * dirichlet_bc%rectangle%vertices(:,i)
Expand All @@ -708,13 +725,14 @@ END SUBROUTINE create_aa_planar_dbc
!> \param zeta the mollifier's width
!> \param dbc_id unique ID for the planar Dirichlet region
!> \param dirichlet_bc the dirichlet_bc object to be created
!> \param debug whether or not to print out the coordinates of the vertices
!> \param error cp2k error
!> \par History
!> 08.2014 created [Hossein Bani-Hashemian]
!> \author Mohammad Hossein Bani-Hashemian
! *****************************************************************************
SUBROUTINE create_arbitrary_planar_dbc(x_glbl, y_glbl, z_glbl, A, B, C, v_D, &
smooth, zeta, dbc_id, dirichlet_bc, error)
smooth, zeta, dbc_id, dirichlet_bc, debug, error)

REAL(dp), ALLOCATABLE, DIMENSION(:), &
INTENT(IN) :: x_glbl, y_glbl, z_glbl
Expand All @@ -725,6 +743,7 @@ SUBROUTINE create_arbitrary_planar_dbc(x_glbl, y_glbl, z_glbl, A, B, C, v_D, &
INTEGER, INTENT(IN) :: dbc_id
TYPE(dirichlet_bc_type), INTENT(INOUT), &
POINTER :: dirichlet_bc
LOGICAL, INTENT(IN) :: debug
TYPE(cp_error_type), INTENT(INOUT) :: error

CHARACTER(LEN=*), PARAMETER :: routineN = 'create_arbitrary_planar_dbc', &
Expand Down Expand Up @@ -812,6 +831,7 @@ SUBROUTINE create_arbitrary_planar_dbc(x_glbl, y_glbl, z_glbl, A, B, C, v_D, &
dirichlet_bc%mollifier_zeta = zeta

IF ((unit_nr .GT. 0) .AND. debug) THEN
WRITE(unit_nr, '(T3,A,A)') "======== debug ", REPEAT('=', 63)
DO i = 1, 4
WRITE(unit_nr,'(T10,A,I1,3F10.3)') " vertex ", i, &
angstrom * dirichlet_bc%rectangle%vertices(:,i)
Expand All @@ -835,13 +855,14 @@ END SUBROUTINE create_arbitrary_planar_dbc
!> \param zeta the mollifier's width
!> \param dbc_id unique ID for the planar Dirichlet region
!> \param dirichlet_bc the dirichlet_bc object to be created
!> \param debug whether or not to print out the coordinates of the vertices
!> \param error cp2k error
!> \par History
!> 12.2014 created [Hossein Bani-Hashemian]
!> \author Mohammad Hossein Bani-Hashemian
! *****************************************************************************
SUBROUTINE create_aa_cuboidal_dbc(x_glbl, y_glbl, z_glbl, x_xtnt, y_xtnt, z_xtnt, &
v_D, smooth, zeta, dbc_id, dirichlet_bc, error)
v_D, smooth, zeta, dbc_id, dirichlet_bc, debug, error)
REAL(dp), ALLOCATABLE, DIMENSION(:), &
INTENT(IN) :: x_glbl, y_glbl, z_glbl
Expand All @@ -852,6 +873,7 @@ SUBROUTINE create_aa_cuboidal_dbc(x_glbl, y_glbl, z_glbl, x_xtnt, y_xtnt, z_xtnt
INTEGER, INTENT(IN) :: dbc_id
TYPE(dirichlet_bc_type), INTENT(INOUT), &
POINTER :: dirichlet_bc
LOGICAL, INTENT(IN) :: debug
TYPE(cp_error_type), INTENT(INOUT) :: error
CHARACTER(LEN=*), PARAMETER :: routineN = 'create_aa_cuboidal_dbc', &
Expand Down Expand Up @@ -937,6 +959,7 @@ SUBROUTINE create_aa_cuboidal_dbc(x_glbl, y_glbl, z_glbl, x_xtnt, y_xtnt, z_xtnt
dirichlet_bc%n_tiles = 1
IF ((unit_nr .GT. 0) .AND. debug) THEN
WRITE(unit_nr, '(T3,A,A)') "======== debug ", REPEAT('=', 63)
DO i = 1, 8
WRITE(unit_nr,'(T10,A,I1,3F10.3)') " vertex ", i, angstrom * dirichlet_bc%box%vertices(:,i)
END DO
Expand Down

0 comments on commit e2f0567

Please sign in to comment.