(git:07c9450)
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-2025 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 zeff ...
40!> \param stride ...
41!> \param max_file_size_mb ...
42!> \param zero_tails ...
43!> \param silent minimal I/O
44!> \param mpi_io True if cube should be written in parallel using MPI
45! **************************************************************************************************
46 SUBROUTINE cp_pw_to_cube(pw, unit_nr, title, particles, zeff, stride, max_file_size_mb, &
47 zero_tails, silent, mpi_io)
48 TYPE(pw_r3d_rs_type), INTENT(IN) :: pw
49 INTEGER, INTENT(IN) :: unit_nr
50 CHARACTER(*), INTENT(IN), OPTIONAL :: title
51 TYPE(particle_list_type), POINTER :: particles
52 REAL(kind=dp), DIMENSION(:), OPTIONAL :: zeff
53 INTEGER, DIMENSION(:), OPTIONAL, POINTER :: stride
54 REAL(kind=dp), INTENT(IN), OPTIONAL :: max_file_size_mb
55 LOGICAL, INTENT(IN), OPTIONAL :: zero_tails, silent, mpi_io
56
57 INTEGER :: i, n
58 INTEGER, ALLOCATABLE, DIMENSION(:) :: particles_z
59 REAL(kind=dp), ALLOCATABLE, DIMENSION(:, :) :: particles_r
60 TYPE(particle_list_type), POINTER :: my_particles
61
62 NULLIFY (my_particles)
63 my_particles => particles
64 IF (ASSOCIATED(my_particles)) THEN
65 n = my_particles%n_els
66 ALLOCATE (particles_z(n))
67 ALLOCATE (particles_r(3, n))
68 DO i = 1, n
69 CALL get_atomic_kind(my_particles%els(i)%atomic_kind, z=particles_z(i))
70 particles_r(:, i) = my_particles%els(i)%r(:)
71 END DO
72
73 CALL pw_to_cube(pw=pw, unit_nr=unit_nr, title=title, &
74 particles_z=particles_z, particles_r=particles_r, &
75 particles_zeff=zeff, &
76 stride=stride, max_file_size_mb=max_file_size_mb, &
77 zero_tails=zero_tails, silent=silent, mpi_io=mpi_io)
78 ELSE
79 CALL pw_to_cube(pw=pw, unit_nr=unit_nr, title=title, &
80 stride=stride, max_file_size_mb=max_file_size_mb, &
81 zero_tails=zero_tails, silent=silent, mpi_io=mpi_io)
82 END IF
83
84 END SUBROUTINE cp_pw_to_cube
85
86! **************************************************************************************************
87!> \brief Prints grid in a simple format: X Y Z value
88!> \param pw ...
89!> \param unit_nr ...
90!> \param stride ...
91!> \param pw2 ...
92!> \par History
93!> Created [Vladimir Rybkin] (08.2017)
94! **************************************************************************************************
95 SUBROUTINE cp_pw_to_simple_volumetric(pw, unit_nr, stride, pw2)
96 TYPE(pw_r3d_rs_type), INTENT(IN) :: pw
97 INTEGER, INTENT(IN) :: unit_nr
98 INTEGER, DIMENSION(:), OPTIONAL, POINTER :: stride
99 TYPE(pw_r3d_rs_type), INTENT(IN), OPTIONAL :: pw2
100
101 IF (.NOT. PRESENT(pw2)) THEN
102 CALL pw_to_simple_volumetric(pw, unit_nr, stride)
103 ELSE
104 CALL pw_to_simple_volumetric(pw, unit_nr, stride, pw2)
105 END IF
106
107 END SUBROUTINE cp_pw_to_simple_volumetric
108
109! **************************************************************************************************
110!> \brief Thin wrapper around routine cube_to_pw
111!> \param grid pw to read from cube file
112!> \param filename name of cube file
113!> \param scaling scale values before storing
114!> \param silent minimal I/O
115!> \par History
116!> Created [Nico Holmberg] (09.2018)
117! **************************************************************************************************
118 SUBROUTINE cp_cube_to_pw(grid, filename, scaling, silent)
119 TYPE(pw_r3d_rs_type), INTENT(IN) :: grid
120 CHARACTER(len=*), INTENT(in) :: filename
121 REAL(kind=dp), INTENT(in) :: scaling
122 LOGICAL, INTENT(in), OPTIONAL :: silent
123
124 LOGICAL :: parallel_read
125
126 ! Determine whether to use MPI I/O for reading cube filename
127 parallel_read = .true.
128 ! Parallel routine falls back to stream read in serial mode,
129 ! but it has slight overhead compared to sequential read
130 ! Therefore, we use sequential version in serial mode
131 IF (grid%pw_grid%para%group%num_pe == 1) parallel_read = .false.
132 ! Check if MPI I/O was disabled in GLOBAL section
133 IF (.NOT. cp_mpi_io_get()) parallel_read = .false.
134
135 CALL cube_to_pw(grid, filename, scaling, parallel_read, silent=silent)
136
137 END SUBROUTINE cp_cube_to_pw
138
139END 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_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.
subroutine, public cp_pw_to_cube(pw, unit_nr, title, particles, zeff, stride, max_file_size_mb, zero_tails, silent, mpi_io)
...
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, particles_zeff, stride, max_file_size_mb, zero_tails, silent, mpi_io)
...