LCOV - code coverage report
Current view: top level - src - tip_scan_types.F (source / functions) Hit Total Coverage
Test: CP2K Regtests (git:e7e05ae) Lines: 0 85 0.0 %
Date: 2024-04-18 06:59:28 Functions: 0 4 0.0 %

          Line data    Source code
       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             : MODULE tip_scan_types
       9             :    USE input_section_types,             ONLY: section_vals_type,&
      10             :                                               section_vals_val_get
      11             :    USE kinds,                           ONLY: default_string_length,&
      12             :                                               dp
      13             :    USE pw_types,                        ONLY: pw_c1d_gs_type,&
      14             :                                               pw_r3d_rs_type
      15             : #include "./base/base_uses.f90"
      16             : 
      17             :    IMPLICIT NONE
      18             : 
      19             :    PRIVATE
      20             : 
      21             :    CHARACTER(len=*), PARAMETER, PRIVATE :: moduleN = 'tip_scan_types'
      22             : 
      23             :    PUBLIC :: scanning_type, release_scanning_type, read_scanning_section
      24             : 
      25             : ! **************************************************************************************************
      26             :    TYPE scanning_type
      27             :       INTEGER                              :: num_scan_points
      28             :       REAL(KIND=dp), DIMENSION(3)          :: ref_point
      29             :       REAL(KIND=dp), DIMENSION(:, :), &
      30             :          ALLOCATABLE                       :: tip_pos
      31             :       CHARACTER(LEN=default_string_length) :: tip_cube_file
      32             :       TYPE(pw_r3d_rs_type), POINTER               :: tip_pw_r
      33             :       TYPE(pw_c1d_gs_type), POINTER               :: tip_pw_g
      34             :    END TYPE scanning_type
      35             : ! **************************************************************************************************
      36             : 
      37             : CONTAINS
      38             : 
      39             : ! **************************************************************************************************
      40             : !> \brief ...
      41             : !> \param scan_info ...
      42             : !> \param input_section ...
      43             : ! **************************************************************************************************
      44           0 :    SUBROUTINE read_scanning_section(scan_info, input_section)
      45             : 
      46             :       TYPE(scanning_type), INTENT(INOUT)                 :: scan_info
      47             :       TYPE(section_vals_type), POINTER                   :: input_section
      48             : 
      49             :       CHARACTER(LEN=default_string_length)               :: schar
      50             :       INTEGER                                            :: ii, ix, iy, iz, nx, ny, nz
      51           0 :       INTEGER, DIMENSION(:), POINTER                     :: ilist
      52             :       REAL(KIND=dp)                                      :: dx, dy, dz
      53           0 :       REAL(KIND=dp), DIMENSION(:), POINTER               :: rlist, rpoint
      54             : 
      55           0 :       CALL section_vals_val_get(input_section, "SCAN_DIRECTION", c_val=schar)
      56           0 :       CALL section_vals_val_get(input_section, "REFERENCE_POINT", r_vals=rpoint)
      57           0 :       CALL section_vals_val_get(input_section, "SCAN_POINTS", i_vals=ilist)
      58           0 :       CALL section_vals_val_get(input_section, "SCAN_STEP", r_vals=rlist)
      59             : 
      60           0 :       nx = 1
      61           0 :       ny = 1
      62           0 :       nz = 1
      63             : 
      64           0 :       dx = 0.0_dp
      65           0 :       dy = 0.0_dp
      66           0 :       dz = 0.0_dp
      67             : 
      68           0 :       SELECT CASE (schar)
      69             :       CASE ("X")
      70           0 :          CPASSERT(SIZE(ilist) >= 1)
      71           0 :          CPASSERT(SIZE(rlist) >= 1)
      72           0 :          nx = ilist(1)
      73           0 :          dx = rlist(1)
      74             :       CASE ("Y")
      75           0 :          CPASSERT(SIZE(ilist) >= 1)
      76           0 :          CPASSERT(SIZE(rlist) >= 1)
      77           0 :          ny = ilist(1)
      78           0 :          dy = rlist(1)
      79             :       CASE ("Z")
      80           0 :          CPASSERT(SIZE(ilist) >= 1)
      81           0 :          CPASSERT(SIZE(rlist) >= 1)
      82           0 :          nz = ilist(1)
      83           0 :          dz = rlist(1)
      84             :       CASE ("XY")
      85           0 :          CPASSERT(SIZE(ilist) >= 2)
      86           0 :          CPASSERT(SIZE(rlist) >= 2)
      87           0 :          nx = ilist(1)
      88           0 :          ny = ilist(2)
      89           0 :          dx = rlist(1)
      90           0 :          dy = rlist(2)
      91             :       CASE ("XZ")
      92           0 :          CPASSERT(SIZE(ilist) >= 2)
      93           0 :          CPASSERT(SIZE(rlist) >= 2)
      94           0 :          nx = ilist(1)
      95           0 :          nz = ilist(2)
      96           0 :          dx = rlist(1)
      97           0 :          dz = rlist(2)
      98             :       CASE ("YZ")
      99           0 :          CPASSERT(SIZE(ilist) >= 2)
     100           0 :          CPASSERT(SIZE(rlist) >= 2)
     101           0 :          ny = ilist(1)
     102           0 :          nz = ilist(2)
     103           0 :          dy = rlist(1)
     104           0 :          dz = rlist(2)
     105             :       CASE ("XYZ")
     106           0 :          CPASSERT(SIZE(ilist) >= 3)
     107           0 :          CPASSERT(SIZE(rlist) >= 3)
     108           0 :          nx = ilist(1)
     109           0 :          ny = ilist(2)
     110           0 :          nz = ilist(3)
     111           0 :          dx = rlist(1)
     112           0 :          dy = rlist(2)
     113           0 :          dz = rlist(3)
     114             :       CASE DEFAULT
     115           0 :          CPABORT("Invalid Scan Type")
     116             :       END SELECT
     117             : 
     118           0 :       scan_info%ref_point(1:3) = rpoint(1:3)
     119           0 :       scan_info%num_scan_points = nx*ny*nz
     120           0 :       ALLOCATE (scan_info%tip_pos(3, nx*ny*nz))
     121           0 :       rpoint(1) = rpoint(1) - 0.5_dp*(nx - 1)*dx
     122           0 :       rpoint(2) = rpoint(2) - 0.5_dp*(ny - 1)*dy
     123           0 :       rpoint(3) = rpoint(3) - 0.5_dp*(nz - 1)*dz
     124             : 
     125           0 :       ii = 0
     126           0 :       DO iz = 1, nz
     127           0 :          DO iy = 1, ny
     128           0 :             DO ix = 1, nx
     129           0 :                ii = ii + 1
     130           0 :                scan_info%tip_pos(1, ii) = rpoint(1) + (ix - 1)*dx
     131           0 :                scan_info%tip_pos(2, ii) = rpoint(2) + (iy - 1)*dy
     132           0 :                scan_info%tip_pos(3, ii) = rpoint(3) + (iz - 1)*dz
     133             :             END DO
     134             :          END DO
     135             :       END DO
     136             : 
     137             :       ! tip potential file name
     138           0 :       CALL section_vals_val_get(input_section, "TIP_FILENAME", c_val=schar)
     139           0 :       scan_info%tip_cube_file = schar
     140             : 
     141           0 :       NULLIFY (scan_info%tip_pw_r)
     142           0 :       NULLIFY (scan_info%tip_pw_g)
     143             : 
     144           0 :    END SUBROUTINE read_scanning_section
     145             : 
     146             : ! **************************************************************************************************
     147             : !> \brief ...
     148             : !> \param scan_info ...
     149             : ! **************************************************************************************************
     150           0 :    SUBROUTINE release_scanning_type(scan_info)
     151             : 
     152             :       TYPE(scanning_type), INTENT(INOUT)                 :: scan_info
     153             : 
     154           0 :       scan_info%num_scan_points = 0
     155           0 :       scan_info%ref_point = 0.0_dp
     156           0 :       IF (ALLOCATED(scan_info%tip_pos)) THEN
     157           0 :          DEALLOCATE (scan_info%tip_pos)
     158             :       END IF
     159           0 :       IF (ASSOCIATED(scan_info%tip_pw_r)) THEN
     160           0 :          CALL scan_info%tip_pw_r%release()
     161           0 :          DEALLOCATE (scan_info%tip_pw_r)
     162             :       END IF
     163           0 :       IF (ASSOCIATED(scan_info%tip_pw_g)) THEN
     164           0 :          CALL scan_info%tip_pw_g%release()
     165           0 :          DEALLOCATE (scan_info%tip_pw_g)
     166             :       END IF
     167             : 
     168           0 :    END SUBROUTINE release_scanning_type
     169             : 
     170           0 : END MODULE tip_scan_types

Generated by: LCOV version 1.15