RMPCDMD
planar_fields.f90
Go to the documentation of this file.
1 ! This file is part of RMPCDMD
2 ! Copyright (c) 2017 Pierre de Buyl and contributors
3 ! License: BSD 3-clause (see file LICENSE)
4 
6 
8  use common
10  use cell_system
11  use neighbor_list
12  implicit none
13 
14  private
15 
16  public :: planar_fields_t
17 
19  double precision, allocatable :: count(:,:,:)
20  double precision, allocatable :: v(:,:,:,:)
21  double precision :: x_min, dx
22  double precision :: y_min, dy
23  double precision :: thickness
24  type(timer_t), pointer :: timer
25  contains
26  procedure :: init
27  procedure :: update
28  end type planar_fields_t
29 
30 contains
31 
33  subroutine init(this, N_species, N_x, x_min, x_max, N_y, y_min, y_max, thickness)
34  class(planar_fields_t), intent(out) :: this
35  integer, intent(in) :: N_species
36  integer, intent(in) :: N_x
37  double precision, intent(in) :: x_min
38  double precision, intent(in) :: x_max
39  integer, intent(in) :: N_y
40  double precision, intent(in) :: y_min
41  double precision, intent(in) :: y_max
42  double precision, intent(in) :: thickness
43 
44  allocate(this%count(n_species, n_y, n_x))
45  allocate(this%v(2, n_species, n_y, n_x))
46 
47  this%count = 0
48  this%v = 0
49 
50  this%x_min = x_min
51  this%dx = (x_max-x_min) / n_x
52  this%y_min = y_min
53  this%dy = (y_max-y_min) / n_y
54  this%thickness = thickness
55 
56  allocate(this%timer)
57  call this%timer%init('planar_update')
58 
59  end subroutine init
60 
62  subroutine update(this, x, v, one_x, one_y, one_z, omega, solvent, cells)
63  class(planar_fields_t), intent(inout) :: this
64  double precision, intent(in) :: x(3)
65  double precision, intent(in) :: v(3)
66  double precision, intent(in) :: one_x(3)
67  double precision, intent(in) :: one_y(3)
68  double precision, intent(in) :: one_z(3)
69  double precision, intent(in) :: omega(3)
70  type(particle_system_t), intent(in) :: solvent
71  type(cell_system_t), intent(in) :: cells
72 
73  double precision :: x_min, x_max, dx, y_min, y_max, dy, z_max
74  double precision :: body_x, body_y, body_z, v_x, v_y
75  double precision, dimension(3) :: d, L
76  integer :: n_x, n_y, n_species
77  double precision, dimension(3) :: solvent_v
78  integer :: idx, s2, i_x, i_y
79 
80  integer, allocatable :: this_count(:,:,:)
81  double precision, allocatable :: this_v(:,:,:,:)
82 
83  integer :: cell_idx, start, n
84 
85  l = cells%edges
86 
87  n_species = size(this%count, dim=1)
88  n_y = size(this%count, dim=2)
89  n_x = size(this%count, dim=3)
90 
91  x_min = this%x_min
92  dx = this%dx
93  x_max = x_min + n_x*dx
94  y_min = this%y_min
95  dy = this%dy
96  y_max = y_min + n_y*dy
97  z_max = this%thickness/2
98 
99  allocate(this_v(2, n_species, n_y, n_x))
100  allocate(this_count(n_species, n_y, n_x))
101  this_v = 0
102  this_count = 0
103 
104  call this%timer%tic()
105  !$omp parallel do &
106  !$omp private(cell_idx, idx, start, n, s2, d, solvent_v, &
107  !$omp body_x, body_y, body_z, v_x, v_y, i_x, i_y) &
108  !$omp reduction(+:this_v) reduction(+:this_count)
109  do cell_idx = 1, cells%N
110 
111  start = cells% cell_start(cell_idx)
112  n = cells% cell_count(cell_idx)
113 
114  do idx = start, start + n - 1
115  s2 = solvent%species(idx)
116  if (s2 <= 0) cycle
117  d = rel_pos(solvent%pos(:,idx), x, l)
118  body_z = dot_product(d, one_z)
119  if (abs(body_z)>z_max) cycle
120  body_x = dot_product(d, one_x)
121  body_y = dot_product(d, one_y)
122 
123  if ( (body_x > x_min) .and. (body_x < x_max) .and. &
124  (body_y > y_min) .and. (body_y < y_max) ) then
125 
126  i_x = floor((body_x-x_min)/dx)+1
127  i_y = floor((body_y-y_min)/dy)+1
128  solvent_v = solvent%vel(:,idx) - v
129  solvent_v = solvent_v - cross(omega, d)
130  v_x = dot_product(solvent_v, one_x)
131  v_y = dot_product(solvent_v, one_y)
132  this_count(s2, i_y, i_x) = this_count(s2, i_y, i_x) + 1
133  this_v(:, s2, i_y, i_x) = this_v(:,s2, i_y, i_x) + [v_x, v_y]
134 
135  end if
136  end do
137  end do
138 
139  this%v = this%v + this_v
140  this%count = this%count + this_count
141 
142  deallocate(this_v)
143  deallocate(this_count)
144 
145  call this%timer%tac()
146 
147  end subroutine update
148 
149 end module planar_fields
Derived type and routines for neighbor listing.
Data for particles.
pure double precision function, dimension(3), public cross(x1, x2)
Definition: common.f90:405
subroutine init(this, L, a, has_walls)
Definition: cell_system.f90:50
Routines to compute planar concentration and velocity profiles.
subroutine update(this, x, v, one_x, one_y, one_z, omega, solvent, cells)
Update the fields.
Utility routines.
Definition: common.f90:12
pure double precision function, dimension(3), public rel_pos(x, y, L)
Return x-y distance with minimum image convention.
Definition: common.f90:163
Spatial cells.
Definition: cell_system.f90:11