MPI-AMRVAC  3.0
The MPI - Adaptive Mesh Refinement - Versatile Advection Code
mod_init_datafromfile.t
Go to the documentation of this file.
1 !> Module to set (or derive) initial conditions from user data
2 !> We read in a vtk file that provides values on grid
5 
6  implicit none
7  private
8 
9  integer, parameter :: max_valuesfromfile = 10
10 
11  type read_data_values
12  integer :: n_variables
13  double precision :: origin(3)
14  double precision :: dx(3)
15  integer :: n_points(3)
16  character(len=40), allocatable :: names(:)
17  double precision, allocatable :: values(:, :, :, :)
18  end type read_data_values
19 
20  type(LT_t) :: lt_1d(max_valuesfromfile)
21  type(LT2_t) :: lt_2d(max_valuesfromfile)
22  type(LT3_t) :: lt_3d(max_valuesfromfile)
23 
24  public :: read_data_init
25  public :: read_data_set
26  public :: read_data_get_1d
27  public :: read_data_get_2d
28  public :: read_data_get_3d
29 
30 contains
31 
32  subroutine read_data_init()
34 
35  integer :: ivar
36  double precision :: xmax(3)
37  type(read_data_values) :: bc
38 
39  if(usr_filename/='')then
40  if(mype==0)then
41  print *,'Reading data from input usr_filename=',usr_filename
42  endif
44  xmax=bc%origin + (bc%n_points-1) * bc%dx
45  if(mype==0)then
46  print *,'Obtained data in ',bc%n_points,' grid with spacings ',bc%dx,' for number of vars=',bc%n_variables
47  endif
48 
49  do ivar = 1,bc%n_variables
50  {^ifoned
51  lt_1d(ivar) = lt_create_from_data(bc%origin(1), &
52  xmax(1), bc%values(:, 1, 1:1, ivar))
53  }
54  {^iftwod
55  lt_2d(ivar) = lt2_create_from_data(bc%origin(1:ndim), &
56  xmax(1:ndim), bc%values(:, :, 1:1, ivar))
57  }
58  {^ifthreed
59  lt_3d(ivar) = lt3_create_from_data(bc%origin(1:ndim), &
60  xmax(1:ndim), bc%values(:, :, :, ivar:ivar))
61  }
62  end do
63  endif
64 
65  end subroutine read_data_init
66 
67  elemental function read_data_get_3d(ivar, x1, x2, x3) result(val)
68  integer, intent(in) :: ivar
69  double precision, intent(in) :: x1, x2, x3
70  double precision :: val
71 
72  val = lt3_get_col(lt_3d(ivar), 1, x1, x2, x3)
73  end function read_data_get_3d
74 
75  elemental function read_data_get_2d(ivar, x1, x2) result(val)
76  integer, intent(in) :: ivar
77  double precision, intent(in) :: x1, x2
78  double precision :: val
79 
80  val = lt2_get_col(lt_2d(ivar), 1, x1, x2)
81  end function read_data_get_2d
82 
83  elemental function read_data_get_1d(ivar, x1) result(val)
84  integer, intent(in) :: ivar
85  double precision, intent(in) :: x1
86  double precision :: val
87 
88  val = lt_get_col(lt_1d(ivar), 1, x1)
89  end function read_data_get_1d
90 
91  !> Set values according to user data
92  subroutine read_data_set(ixI^L,ixO^L,x,val,nval)
94  integer, intent(in) :: ixi^l, ixo^l, nval
95  double precision, intent(in) :: x(ixi^s,1:ndim)
96  double precision, intent(out) :: val(ixi^s,1:nval)
97  integer :: ival
98 
99  {^ifoned
100  do ival=1,nval
101  val(ixomin1:ixomax1,ival) = read_data_get_1d(ival,x(ixomin1:ixomax1,1))
102  enddo
103  }
104  {^iftwod
105  do ival=1,nval
106  val(ixomin1:ixomax1, ixomin2:ixomax2, ival) = read_data_get_2d(ival, &
107  x(ixomin1:ixomax1, ixomin2:ixomax2, 1), x(ixomin1:ixomax1, ixomin2:ixomax2, 2))
108  enddo
109  }
110  {^ifthreed
111  do ival=1,nval
112  val(ixomin1:ixomax1, ixomin2:ixomax2, ixomin3:ixomax3, ival) = read_data_get_3d(ival, &
113  x(ixomin1:ixomax1, ixomin2:ixomax2, ixomin3:ixomax3, 1), &
114  x(ixomin1:ixomax1, ixomin2:ixomax2, ixomin3:ixomax3, 2), &
115  x(ixomin1:ixomax1, ixomin2:ixomax2, ixomin3:ixomax3, 3))
116  enddo
117  }
118 
119  end subroutine read_data_set
120 
121  subroutine read_vtk_structured_points(fname, bc)
122  character(len=*), intent(in) :: fname
123  type(read_data_values), intent(out) :: bc
124  double precision, allocatable :: tmp_data(:, :, :, :)
125  integer, parameter :: max_variables = 10
126  character(len=40) :: tmp_names(max_variables)
127  character(len=256) :: line
128  character(len=40) :: word, typename
129  integer, parameter :: my_unit = 123
130  integer :: n, n_points_total
131  integer :: n_components
132 
133  open(my_unit, file=trim(fname), status="old", action="read")
134 
135  ! Header, e.g. # vtk DataFile Version 2.0
136  read(my_unit, "(A)") line
137 
138  ! Dataset name
139  read(my_unit, "(A)") line
140 
141  ! ASCII / BINARY
142  read(my_unit, "(A)") line
143 
144  if (line /= "ASCII") then
145  print *, "line: ", trim(line)
146  error stop "read_vtk: not an ASCII file"
147  end if
148 
149  ! DATASET STRUCTURED_POINTS
150  read(my_unit, "(A)") line
151 
152  if (line /= "DATASET STRUCTURED_POINTS") then
153  print *, "line: ", trim(line)
154  error stop "read_vtk must have: DATASET STRUCTURED_POINTS"
155  end if
156 
157  ! DIMENSIONS NX NY NZ
158  read(my_unit, "(A)") line
159  read(line, *) word, bc%n_points
160 
161  if (word /= "DIMENSIONS") then
162  print *, "line: ", trim(line)
163  error stop "read_vtk expects: DIMENSIONS"
164  end if
165 
166  ! SPACING DX DY DZ
167  read(my_unit, *) word, bc%dx
168 
169  if (word /= "SPACING") then
170  print *, "line: ", trim(line)
171  error stop "read_vtk expects: SPACING"
172  end if
173 
174  ! ORIGIN 0 0 0
175  read(my_unit, *) word, bc%origin
176  if (word /= "ORIGIN") then
177  print *, "line: ", trim(line)
178  error stop "read_vtk expects: ORIGIN"
179  end if
180 
181  ! POINT_DATA NPOINTS
182  read(my_unit, *) word, n_points_total
183 
184  if (word /= "POINT_DATA") then
185  print *, "line: ", trim(line)
186  error stop "read_vtk expects: POINT_DATA n_points"
187  end if
188 
189  if (n_points_total /= product(bc%n_points)) &
190  error stop "read_vtk: n_points not equal to NX*NY*NZ"
191 
192  allocate(tmp_data(bc%n_points(1), bc%n_points(2), bc%n_points(3), &
193  max_variables))
194 
195  ! Read all scalar variables
196  do n = 1, max_variables
197 
198  ! SCALARS name type ncomponents
199  read(my_unit, *, end=900) word, tmp_names(n), typename, n_components
200 
201  if (word /= "SCALARS") then
202  print *, "line: ", trim(line)
203  error stop "read_vtk expects: SCALARS name type ncomponents"
204  end if
205 
206  if (n_components /= 1) error stop "read_vtk: ncomponents should be 1"
207 
208  ! LOOKUP_TABLE default
209  read(my_unit, *) word, typename
210 
211  if (word /= "LOOKUP_TABLE") then
212  print *, "line: ", trim(line)
213  error stop "read_vtk expects: LOOKUP_TABLE name"
214  end if
215 
216  ! Read list of data values
217  read(my_unit, *) tmp_data(:, :, :, n)
218  end do
219 
220  ! Done reading variables
221 900 continue
222 
223  close(my_unit)
224 
225  if (n == max_variables + 1) &
226  error stop "read_vtk: increase max_variables"
227 
228  ! Loop index is one higher than number of variables
229  bc%n_variables = n-1
230  bc%values = tmp_data(:, :, :, 1:n-1)
231  bc%names = tmp_names(1:n-1)
232  end subroutine read_vtk_structured_points
233 
234 end module mod_init_datafromfile
This module contains definitions of global parameters and variables and some generic functions/subrou...
integer, parameter ndim
Number of spatial dimensions for grid variables.
integer mype
The rank of the current MPI task.
character(len=std_len) usr_filename
User parameter file.
Module to set (or derive) initial conditions from user data We read in a vtk file that provides value...
elemental double precision function, public read_data_get_2d(ivar, x1, x2)
elemental double precision function, public read_data_get_3d(ivar, x1, x2, x3)
subroutine, public read_data_set(ixIL, ixOL, x, val, nval)
Set values according to user data.
subroutine read_vtk_structured_points(fname, bc)
elemental double precision function, public read_data_get_1d(ivar, x1)
subroutine, public read_data_init()
A Fortran 90 module for creating 1D and 2D lookup tables. These tables can be used to efficiently int...
type(lt2_t) function, public lt2_create_from_data(x_min, x_max, spaced_data)
This function returns a new lookup table from regularly spaced data.
elemental real(dp) function, public lt_get_col(my_lt, col_ix, x)
Get the value of a single column at x.
elemental real(dp) function, public lt2_get_col(my_lt, col_ix, x1, x2)
Get the value of a single column at x.
elemental real(dp) function, public lt3_get_col(my_lt, col_ix, x1, x2, x3)
Get the value of a single column at x.
type(lt_t) function, public lt_create_from_data(x_min, x_max, spaced_data)
This function returns a new lookup table from regularly spaced data.
type(lt3_t) function, public lt3_create_from_data(x_min, x_max, spaced_data)
This function returns a new lookup table from regularly spaced data.