File: test_fortran_create_atoms.f90

package info (click to toggle)
lammps 20250204%2Bdfsg.1-2
  • links: PTS, VCS
  • area: main
  • in suites: forky, sid, trixie
  • size: 474,368 kB
  • sloc: cpp: 1,060,070; python: 27,785; ansic: 8,956; f90: 7,254; sh: 6,044; perl: 4,171; fortran: 2,442; xml: 1,714; makefile: 1,352; objc: 238; lisp: 188; yacc: 58; csh: 16; awk: 14; tcl: 6; javascript: 2
file content (157 lines) | stat: -rw-r--r-- 5,654 bytes parent folder | download
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
FUNCTION f_lammps_with_args() BIND(C)
  USE, INTRINSIC :: ISO_C_BINDING, ONLY: c_ptr
  USE LIBLAMMPS
  USE keepstuff, ONLY: lmp
  IMPLICIT NONE
  TYPE(c_ptr) :: f_lammps_with_args
  CHARACTER(len=12), DIMENSION(12), PARAMETER :: args = &
      [ CHARACTER(len=12) :: 'liblammps', '-log', 'none', &
      '-echo','screen','-nocite','-var','zpos','1.5','-var','x','2']

  lmp = lammps(args)
  f_lammps_with_args = lmp%handle
END FUNCTION f_lammps_with_args

SUBROUTINE f_lammps_close() BIND(C)
  USE, INTRINSIC :: ISO_C_BINDING, ONLY: c_null_ptr
  USE liblammps
  USE keepstuff, ONLY: lmp
  IMPLICIT NONE

  CALL lmp%close()
  lmp%handle = c_null_ptr
END SUBROUTINE f_lammps_close

SUBROUTINE f_lammps_setup_create_atoms() BIND(C)
  USE LIBLAMMPS
  USE keepstuff, ONLY : lmp, big_input, cont_input, more_input
  IMPLICIT NONE

  !CALL lmp%command('atom_modify map array')
  CALL lmp%commands_list(big_input)
  CALL lmp%commands_list(cont_input)
  CALL lmp%commands_list(more_input)
END SUBROUTINE f_lammps_setup_create_atoms

SUBROUTINE f_lammps_create_three_atoms() BIND(C)
  USE, INTRINSIC :: ISO_C_BINDING, ONLY: c_double, c_int, c_int64_t
  USE keepstuff, ONLY : lmp
  USE LIBLAMMPS
  IMPLICIT NONE
  INTEGER(c_int), DIMENSION(3) :: new_ids, new_images, new_types
  INTEGER(c_int64_t), DIMENSION(3) :: new_big_ids, new_big_images
  REAL(c_double), DIMENSION(9) :: new_x, new_v
  LOGICAL :: wrap
  INTEGER(c_int) :: tagint_size

  new_ids = [4, 6, 5]
  new_big_ids = [4, 6, 5]
  tagint_size = lmp%extract_setting('tagint')
  IF ( tagint_size == 4_c_int ) THEN
    new_images(1) = lmp%encode_image_flags(1, -1, 3)
    new_images(2) = lmp%encode_image_flags(-2, 0, 0)
    new_images(3) = lmp%encode_image_flags(-2, -2, 1)
  ELSE
    new_big_images(1) = lmp%encode_image_flags(1, -1, 3)
    new_big_images(2) = lmp%encode_image_flags(-2, 0, 0)
    new_big_images(3) = lmp%encode_image_flags(-2, -2, 1)
  END IF
  new_types = [1, 1, 1]
  new_x = [ 1.0_c_double, 1.8_c_double, 2.718281828_c_double, &
            0.6_c_double, 0.8_c_double, 2.2_c_double, &
            1.8_c_double, 0.1_c_double, 1.8_c_double ]
  new_v = [ 0.0_c_double, 1.0_c_double, -1.0_c_double, &
            0.1_c_double, 0.2_c_double, -0.2_c_double, &
            1.0_c_double, -1.0_c_double, 3.0_c_double ]
  wrap = .FALSE.
  IF ( tagint_size == 4_c_int ) THEN
    CALL lmp%create_atoms(new_ids, new_types, new_x, new_v, new_images, wrap)
  ELSE
    CALL lmp%create_atoms(new_big_ids, new_types, new_x, new_v, &
      new_big_images, wrap)
  END IF
END SUBROUTINE f_lammps_create_three_atoms

SUBROUTINE f_lammps_create_two_more() BIND(C)
  USE, INTRINSIC :: ISO_C_BINDING, ONLY: c_double, c_int
  USE keepstuff, ONLY : lmp
  USE LIBLAMMPS
  IMPLICIT NONE
  INTEGER(c_int), DIMENSION(2) :: new_types
  REAL(c_double), DIMENSION(6) :: new_x

  new_types = [1_c_int, 1_c_int]
  new_x = [0.1_c_double, 1.9_c_double, 3.8_c_double, &
           1.2_c_double, 2.1_c_double, 1.25_c_double]
  CALL lmp%create_atoms(type=new_types, x=new_x)
END SUBROUTINE f_lammps_create_two_more

SUBROUTINE f_lammps_create_two_more_small() BIND(C)
  USE, INTRINSIC :: ISO_C_BINDING, ONLY: c_double, c_int
  USE keepstuff, ONLY : lmp
  USE LIBLAMMPS
  IMPLICIT NONE
  INTEGER(c_int), DIMENSION(2) :: new_types
  REAL(c_double), DIMENSION(6) :: new_x
  INTEGER(c_int), DIMENSION(2) :: new_id, new_image

  new_types = [1_c_int, 1_c_int]
  new_x = [0.1_c_double, 1.9_c_double, 3.8_c_double, &
           1.2_c_double, 2.1_c_double, 1.25_c_double]
  new_id = [8_c_int, 7_c_int]
  new_image(1) = lmp%encode_image_flags(1,0,0)
  new_image(2) = lmp%encode_image_flags(-1,0,0)
  CALL lmp%create_atoms(id=new_id, image=new_image, type=new_types, x=new_x)
END SUBROUTINE f_lammps_create_two_more_small

SUBROUTINE f_lammps_create_two_more_big() BIND(C)
  USE, INTRINSIC :: ISO_C_BINDING, ONLY: c_double, c_int, c_int64_t
  USE keepstuff, ONLY : lmp
  USE LIBLAMMPS
  IMPLICIT NONE
  INTEGER(c_int), DIMENSION(2) :: new_types
  REAL(c_double), DIMENSION(6) :: new_x
  INTEGER(c_int64_t), DIMENSION(2) :: new_id, new_image

  new_types = [1_c_int, 1_c_int]
  new_x = [0.1_c_double, 1.9_c_double, 3.8_c_double, &
           1.2_c_double, 2.1_c_double, 1.25_c_double]
  new_id = [8_c_int64_t, 7_c_int64_t]
  new_image(1) = lmp%encode_image_flags(1,0,0)
  new_image(2) = lmp%encode_image_flags(-1,0,0)
  CALL lmp%create_atoms(id=new_id, image=new_image, type=new_types, x=new_x)
END SUBROUTINE f_lammps_create_two_more_big

SUBROUTINE f_lammps_create_two_more_small2() BIND(C)
  USE, INTRINSIC :: ISO_C_BINDING, ONLY: c_double, c_int
  USE keepstuff, ONLY : lmp
  USE LIBLAMMPS
  IMPLICIT NONE
  INTEGER(c_int), DIMENSION(2) :: new_types
  REAL(c_double), DIMENSION(6) :: new_x
  INTEGER(c_int), DIMENSION(2) :: new_id

  new_types = [1_c_int, 1_c_int]
  new_x = [0.1_c_double, 1.9_c_double, 3.8_c_double, &
           1.2_c_double, 2.1_c_double, 1.25_c_double]
  new_id = [8_c_int, 7_c_int]
  CALL lmp%create_atoms(id=new_id, type=new_types, x=new_x)
END SUBROUTINE f_lammps_create_two_more_small2

SUBROUTINE f_lammps_create_two_more_big2() BIND(C)
  USE, INTRINSIC :: ISO_C_BINDING, ONLY: c_double, c_int, c_int64_t
  USE keepstuff, ONLY : lmp
  USE LIBLAMMPS
  IMPLICIT NONE
  INTEGER(c_int), DIMENSION(2) :: new_types
  REAL(c_double), DIMENSION(6) :: new_x
  INTEGER(c_int64_t), DIMENSION(2) :: new_id

  new_types = [1_c_int, 1_c_int]
  new_x = [0.1_c_double, 1.9_c_double, 3.8_c_double, &
           1.2_c_double, 2.1_c_double, 1.25_c_double]
  new_id = [8_c_int64_t, 7_c_int64_t]
  CALL lmp%create_atoms(id=new_id, type=new_types, x=new_x)
END SUBROUTINE f_lammps_create_two_more_big2

! vim: ts=2 sts=2 sw=2 et