(git:374b731)
Loading...
Searching...
No Matches
cp_realspace_grid_cube.F
Go to the documentation of this file.
1!--------------------------------------------------------------------------------------------------!
2! CP2K: A general program to perform molecular dynamics simulations !
3! Copyright 2000-2024 CP2K developers group <https://cp2k.org> !
4! !
5! SPDX-License-Identifier: GPL-2.0-or-later !
6!--------------------------------------------------------------------------------------------------!
7
8! **************************************************************************************************
9!> \brief A wrapper around pw_to_cube() which accepts particle_list_type
10!> \author Ole Schuett
11! **************************************************************************************************
15 USE kinds, ONLY: dp
17 USE pw_types, ONLY: pw_r3d_rs_type
21#include "./base/base_uses.f90"
22
23 IMPLICIT NONE
24
25 PRIVATE
26
28
29 CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'cp_realspace_grid_cube'
30
31CONTAINS
32
33! **************************************************************************************************
34!> \brief ...
35!> \param pw ...
36!> \param unit_nr ...
37!> \param title ...
38!> \param particles ...
39!> \param stride ...
40!> \param zero_tails ...
41!> \param silent minimal I/O
42!> \param mpi_io True if cube should be written in parallel using MPI
43! **************************************************************************************************
44 SUBROUTINE cp_pw_to_cube(pw, unit_nr, title, particles, stride, zero_tails, silent, mpi_io)
45 TYPE(pw_r3d_rs_type), INTENT(IN) :: pw
46 INTEGER, INTENT(IN) :: unit_nr
47 CHARACTER(*), INTENT(IN), OPTIONAL :: title
48 TYPE(particle_list_type), POINTER :: particles
49 INTEGER, DIMENSION(:), OPTIONAL, POINTER :: stride
50 LOGICAL, INTENT(IN), OPTIONAL :: zero_tails, silent, mpi_io
51
52 INTEGER :: i, n
53 INTEGER, ALLOCATABLE, DIMENSION(:) :: particles_z
54 REAL(kind=dp), ALLOCATABLE, DIMENSION(:, :) :: particles_r
55 TYPE(particle_list_type), POINTER :: my_particles
56
57 NULLIFY (my_particles)
58 my_particles => particles
59 IF (ASSOCIATED(my_particles)) THEN
60 n = my_particles%n_els
61 ALLOCATE (particles_z(n))
62 ALLOCATE (particles_r(3, n))
63 DO i = 1, n
64 CALL get_atomic_kind(my_particles%els(i)%atomic_kind, z=particles_z(i))
65 particles_r(:, i) = my_particles%els(i)%r(:)
66 END DO
67
68 CALL pw_to_cube(pw=pw, unit_nr=unit_nr, title=title, &
69 particles_z=particles_z, particles_r=particles_r, &
70 stride=stride, zero_tails=zero_tails, &
71 silent=silent, mpi_io=mpi_io)
72 ELSE
73 CALL pw_to_cube(pw=pw, unit_nr=unit_nr, title=title, &
74 stride=stride, zero_tails=zero_tails, &
75 silent=silent, mpi_io=mpi_io)
76 END IF
77
78 END SUBROUTINE cp_pw_to_cube
79
80! **************************************************************************************************
81!> \brief Prints grid in a simple format: X Y Z value
82!> \param pw ...
83!> \param unit_nr ...
84!> \param stride ...
85!> \param pw2 ...
86!> \par History
87!> Created [Vladimir Rybkin] (08.2017)
88! **************************************************************************************************
89 SUBROUTINE cp_pw_to_simple_volumetric(pw, unit_nr, stride, pw2)
90 TYPE(pw_r3d_rs_type), INTENT(IN) :: pw
91 INTEGER, INTENT(IN) :: unit_nr
92 INTEGER, DIMENSION(:), OPTIONAL, POINTER :: stride
93 TYPE(pw_r3d_rs_type), INTENT(IN), OPTIONAL :: pw2
94
95 IF (.NOT. PRESENT(pw2)) THEN
96 CALL pw_to_simple_volumetric(pw, unit_nr, stride)
97 ELSE
98 CALL pw_to_simple_volumetric(pw, unit_nr, stride, pw2)
99 END IF
100
101 END SUBROUTINE cp_pw_to_simple_volumetric
102
103! **************************************************************************************************
104!> \brief Thin wrapper around routine cube_to_pw
105!> \param grid pw to read from cube file
106!> \param filename name of cube file
107!> \param scaling scale values before storing
108!> \param silent minimal I/O
109!> \par History
110!> Created [Nico Holmberg] (09.2018)
111! **************************************************************************************************
112 SUBROUTINE cp_cube_to_pw(grid, filename, scaling, silent)
113 TYPE(pw_r3d_rs_type), INTENT(IN) :: grid
114 CHARACTER(len=*), INTENT(in) :: filename
115 REAL(kind=dp), INTENT(in) :: scaling
116 LOGICAL, INTENT(in), OPTIONAL :: silent
117
118 LOGICAL :: parallel_read
119
120 ! Determine whether to use MPI I/O for reading cube filename
121 parallel_read = .true.
122 ! Parallel routine falls back to stream read in serial mode,
123 ! but it has slight overhead compared to sequential read
124 ! Therefore, we use sequential version in serial mode
125 IF (grid%pw_grid%para%group_size == 1) parallel_read = .false.
126 ! Check if MPI I/O was disabled in GLOBAL section
127 IF (.NOT. cp_mpi_io_get()) parallel_read = .false.
128
129 CALL cube_to_pw(grid, filename, scaling, parallel_read, silent=silent)
130
131 END SUBROUTINE cp_cube_to_pw
132
133END MODULE cp_realspace_grid_cube
Define the atomic kind types and their sub types.
subroutine, public get_atomic_kind(atomic_kind, fist_potential, element_symbol, name, mass, kind_number, natom, atom_list, rcov, rvdw, z, qeff, apol, cpol, mm_radius, shell, shell_active, damping)
Get attributes of an atomic kind.
routines to handle the output, The idea is to remove the decision of wheter to output and what to out...
logical function, public cp_mpi_io_get()
Gets flag which determines whether or not to use MPI I/O for I/O routines that have been parallized w...
A wrapper around pw_to_cube() which accepts particle_list_type.
subroutine, public cp_pw_to_cube(pw, unit_nr, title, particles, stride, zero_tails, silent, mpi_io)
...
subroutine, public cp_cube_to_pw(grid, filename, scaling, silent)
Thin wrapper around routine cube_to_pw.
subroutine, public cp_pw_to_simple_volumetric(pw, unit_nr, stride, pw2)
Prints grid in a simple format: X Y Z value.
Defines the basic variable types.
Definition kinds.F:23
integer, parameter, public dp
Definition kinds.F:34
represent a simple array based list of the given type
Generate Gaussian cube files.
subroutine, public cube_to_pw(grid, filename, scaling, parallel_read, silent)
Computes the external density on the grid hacked from external_read_density.
subroutine, public pw_to_simple_volumetric(pw, unit_nr, stride, pw2)
Prints a simple grid file: X Y Z value.
subroutine, public pw_to_cube(pw, unit_nr, title, particles_r, particles_z, stride, zero_tails, silent, mpi_io)
...