Neko  0.8.1
A portable framework for high-order spectral element flow simulations
vector.f90
Go to the documentation of this file.
1 ! Copyright (c) 2022, The Neko Authors
2 ! All rights reserved.
3 !
4 ! Redistribution and use in source and binary forms, with or without
5 ! modification, are permitted provided that the following conditions
6 ! are met:
7 !
8 ! * Redistributions of source code must retain the above copyright
9 ! notice, this list of conditions and the following disclaimer.
10 !
11 ! * Redistributions in binary form must reproduce the above
12 ! copyright notice, this list of conditions and the following
13 ! disclaimer in the documentation and/or other materials provided
14 ! with the distribution.
15 !
16 ! * Neither the name of the authors nor the names of its
17 ! contributors may be used to endorse or promote products derived
18 ! from this software without specific prior written permission.
19 !
20 ! THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
21 ! "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
22 ! LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS
23 ! FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE
24 ! COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT,
25 ! INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING,
26 ! BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
27 ! LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
28 ! CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
29 ! LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
30 ! ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
31 ! POSSIBILITY OF SUCH DAMAGE.
32 !
34 module vector
35  use neko_config
36  use num_types
37  use device
39  use utils
40  use, intrinsic :: iso_c_binding
41  implicit none
42  private
43 
44  type, public :: vector_t
45  real(kind=rp), allocatable :: x(:)
46  type(c_ptr) :: x_d = c_null_ptr
47  integer :: n = 0
48  contains
49  procedure, pass(v) :: init => vector_init
50  procedure, pass(v) :: free => vector_free
51  procedure, pass(v) :: size => vector_size
52  procedure, pass(v) :: vector_assign_vector
53  procedure, pass(v) :: vector_assign_scalar
54  generic :: assignment(=) => vector_assign_vector, &
56  end type vector_t
57 
58  type, public :: vector_ptr_t
59  type(vector_t), pointer :: v
60  end type vector_ptr_t
61 
62 contains
63 
65  subroutine vector_init(v, n)
66  class(vector_t), intent(inout) :: v
67  integer, intent(in) :: n
68 
69  call v%free()
70 
71  allocate(v%x(n))
72  v%x = 0.0_rp
73 
74  if (neko_bcknd_device .eq. 1) then
75  call device_map(v%x, v%x_d, n)
76  call device_cfill(v%x_d, 0.0_rp, n)
77  end if
78 
79  v%n = n
80 
81  end subroutine vector_init
82 
84  subroutine vector_free(v)
85  class(vector_t), intent(inout) :: v
86 
87  if (allocated(v%x)) then
88  deallocate(v%x)
89  end if
90 
91  if (c_associated(v%x_d)) then
92  call device_free(v%x_d)
93  end if
94 
95  v%n = 0
96 
97  end subroutine vector_free
98 
100  function vector_size(v) result(s)
101  class(vector_t), intent(inout) :: v
102  integer :: s
103  s = v%n
104  end function vector_size
105 
107  subroutine vector_assign_vector(v, w)
108  class(vector_t), intent(inout) :: v
109  type(vector_t), intent(in) :: w
110 
111  if (allocated(v%x)) then
112  call v%free()
113  end if
114 
115  if (.not. allocated(v%x)) then
116 
117  v%n = w%n
118  allocate(v%x(v%n))
119 
120  if (neko_bcknd_device .eq. 1) then
121  call device_map(v%x, v%x_d, v%n)
122  end if
123 
124  end if
125 
126  if (neko_bcknd_device .eq. 1) then
127  call device_copy(v%x_d, w%x_d, v%n)
128  else
129  v%x = w%x
130  end if
131 
132  end subroutine vector_assign_vector
133 
135  subroutine vector_assign_scalar(v, s)
136  class(vector_t), intent(inout) :: v
137  real(kind=rp), intent(in) :: s
138 
139  if (.not. allocated(v%x)) then
140  call neko_error('Vector not allocated')
141  end if
142 
143  if (neko_bcknd_device .eq. 1) then
144  call device_cfill(v%x_d, s, v%n)
145  else
146  v%x = s
147  end if
148 
149  end subroutine vector_assign_scalar
150 
151 
152 end module vector
Map a Fortran array to a device (allocate and associate)
Definition: device.F90:57
subroutine, public device_copy(a_d, b_d, n)
subroutine, public device_cfill(a_d, c, n)
Device abstraction, common interface for various accelerators.
Definition: device.F90:34
subroutine, public device_free(x_d)
Deallocate memory on the device.
Definition: device.F90:172
Build configurations.
Definition: neko_config.f90:34
integer, parameter neko_bcknd_device
Definition: neko_config.f90:44
integer, parameter, public rp
Global precision used in computations.
Definition: num_types.f90:12
Utilities.
Definition: utils.f90:35
Defines a vector.
Definition: vector.f90:34
subroutine vector_init(v, n)
Initialise a vector of size n.
Definition: vector.f90:66
subroutine vector_assign_scalar(v, s)
Assignment .
Definition: vector.f90:136
integer function vector_size(v)
Return the number of entries in the vector.
Definition: vector.f90:101
subroutine vector_free(v)
Deallocate a vector.
Definition: vector.f90:85
subroutine vector_assign_vector(v, w)
Assignment .
Definition: vector.f90:108