(git:d18deda)
Loading...
Searching...
No Matches
cp_parser_inpp_types.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 module to allow simple internal preprocessing in input files.
10!> \par History
11!> - standalone proof-of-concept implementation (20.02.2008,AK)
12!> - integration into cp2k (22.02.2008,tlaino)
13!> - variables added (25.02.2008,AK)
14!> \author Axel Kohlmeyer [AK] - CMM/UPenn Philadelphia
15!> \date 25.02.2008
16! **************************************************************************************************
18
19 USE kinds, ONLY: default_path_length
20#include "../base/base_uses.f90"
21
22 IMPLICIT NONE
23 PRIVATE
24
26 ! for '@INCLUDE "some_file.inc"'
27 ! currently open include file stack pointer
28 INTEGER :: io_stack_level = 0
29 ! include file stack data
30 INTEGER, POINTER, DIMENSION(:) :: io_stack_channel => null(), &
31 io_stack_lineno => null()
32 CHARACTER(len=default_path_length), &
33 POINTER, DIMENSION(:) :: io_stack_filename => null()
34 ! for '@SET VAR value' and '${VAR}'
35 ! table size
36 INTEGER :: num_variables = 0
37 ! table entries
38 CHARACTER(len=default_path_length), &
39 POINTER, DIMENSION(:) :: variable_name => null()
40 CHARACTER(len=default_path_length), &
41 POINTER, DIMENSION(:) :: variable_value => null()
42 END TYPE inpp_type
43
45 CHARACTER(len=*), PARAMETER, PRIVATE :: modulen = 'cp_parser_inpp_types'
46
47CONTAINS
48
49! ****************************************************************************
50!> \brief creates the internal preprocessing type
51!> \param inpp ...
52!> \param initial_variables ...
53!> \date 22.02.2008
54!> \author Teodoro Laino [tlaino] - University of Zurich
55! **************************************************************************************************
56 SUBROUTINE create_inpp_type(inpp, initial_variables)
57 TYPE(inpp_type), POINTER :: inpp
58 CHARACTER(len=default_path_length), &
59 DIMENSION(:, :), POINTER :: initial_variables
60
61 cpassert(.NOT. ASSOCIATED(inpp))
62 ALLOCATE (inpp)
63
64 IF (ASSOCIATED(initial_variables)) THEN
65 inpp%num_variables = SIZE(initial_variables, 2)
66 ALLOCATE (inpp%variable_name(inpp%num_variables))
67 inpp%variable_name = initial_variables(1, :)
68 ALLOCATE (inpp%variable_value(inpp%num_variables))
69 inpp%variable_value = initial_variables(2, :)
70 END IF
71
72 END SUBROUTINE create_inpp_type
73
74! ****************************************************************************
75!> \brief releases the internal preprocessing type
76!> \param inpp ...
77!> \date 22.02.2008
78!> \author Teodoro Laino [tlaino] - University of Zurich
79! **************************************************************************************************
80 SUBROUTINE release_inpp_type(inpp)
81 TYPE(inpp_type), POINTER :: inpp
82
83 cpassert(ASSOCIATED(inpp))
84
85 IF (ASSOCIATED(inpp%io_stack_channel)) THEN
86 DEALLOCATE (inpp%io_stack_channel)
87 END IF
88 IF (ASSOCIATED(inpp%io_stack_lineno)) THEN
89 DEALLOCATE (inpp%io_stack_lineno)
90 END IF
91 IF (ASSOCIATED(inpp%io_stack_filename)) THEN
92 DEALLOCATE (inpp%io_stack_filename)
93 END IF
94
95 IF (ASSOCIATED(inpp%variable_name)) THEN
96 DEALLOCATE (inpp%variable_name)
97 END IF
98 IF (ASSOCIATED(inpp%variable_value)) THEN
99 DEALLOCATE (inpp%variable_value)
100 END IF
101
102 DEALLOCATE (inpp)
103 END SUBROUTINE release_inpp_type
104
105END MODULE cp_parser_inpp_types
a module to allow simple internal preprocessing in input files.
subroutine, public create_inpp_type(inpp, initial_variables)
creates the internal preprocessing type
subroutine, public release_inpp_type(inpp)
releases the internal preprocessing type
Defines the basic variable types.
Definition kinds.F:23
integer, parameter, public default_path_length
Definition kinds.F:58