Neko  0.8.1
A portable framework for high-order spectral element flow simulations
material_properties.f90
Go to the documentation of this file.
1 ! Copyright (c) 2023, 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 !
35  use num_types, only: rp
36  use json_utils, only : json_get
37  use json_module, only : json_file
41  use utils, only : neko_warning, neko_error
42  use comm, only : pe_rank
43  implicit none
44  private
45 
47  type, public :: material_properties_t
49  real(kind=rp) :: rho
51  real(kind=rp) :: mu
53  real(kind=rp) :: lambda
55  real(kind=rp) :: cp
56  contains
58  procedure, pass(this) :: init => material_properties_init
60  procedure, private, pass(this) :: write_to_log
61  end type material_properties_t
62 
63 contains
64 
67  subroutine material_properties_init(this, params, user)
68  class(material_properties_t), intent(inout) :: this
69  type(json_file), intent(inout) :: params
70  type(user_t), target, intent(in) :: user
71  character(len=LOG_SIZE) :: log_buf
72  ! A local pointer that is needed to make Intel happy
73  procedure(user_material_properties), pointer :: dummy_mp_ptr
74  logical :: nondimensional
75 
76  call neko_log%section('Material properties')
77  dummy_mp_ptr => dummy_user_material_properties
78  nondimensional = .false.
79 
80  if (.not. associated(user%material_properties, dummy_mp_ptr)) then
81 
82  write(log_buf, '(A)') "Material properties must be set in the user&
83  & file!"
84  call neko_log%message(log_buf)
85  call user%material_properties(0.0_rp, 0, this%rho, this%mu, &
86  this%cp, this%lambda, params)
87  else
88 
89  !
90  ! Fluid
91  !
92 
93  ! Incorrect user input
94  if (params%valid_path('case.fluid.Re') .and. &
95  (params%valid_path('case.fluid.mu') .or. &
96  params%valid_path('case.fluid.rho'))) then
97  call neko_error("To set the material properties for the fluid,&
98  & either provide Re OR mu and rho in the case file.")
99 
100  ! Non-dimensional case
101  else if (params%valid_path('case.fluid.Re')) then
102  nondimensional = .true.
103 
104  write(log_buf, '(A)') 'Non-dimensional fluid material properties &
105  & input.'
106  call neko_log%message(log_buf, lvl=neko_log_verbose)
107  write(log_buf, '(A)') 'Density will be set to 1, dynamic viscosity to&
108  & 1/Re.'
109  call neko_log%message(log_buf, lvl=neko_log_verbose)
110 
111  ! Read Re into mu for further manipulation.
112  call json_get(params, 'case.fluid.Re', this%mu)
113  write(log_buf, '(A)') 'Read non-dimensional values:'
114  call neko_log%message(log_buf)
115  write(log_buf, '(A,ES13.6)') 'Re :', this%mu
116  call neko_log%message(log_buf)
117 
118  ! Set rho to 1 since the setup is non-dimensional.
119  this%rho = 1.0_rp
120  ! Invert the Re to get viscosity.
121  this%mu = 1.0_rp/this%mu
122  ! Dimensional case
123  else
124  call json_get(params, 'case.fluid.mu', this%mu)
125  call json_get(params, 'case.fluid.rho', this%rho)
126  end if
127 
128  !
129  ! Scalar
130  !
131  if (.not. params%valid_path('case.scalar')) then
132  ! Set dummy values
133  this%cp = 1.0_rp
134  this%lambda = 1.0_rp
135  call this%write_to_log(.false.)
136  return
137  end if
138 
139  ! Incorrect user input
140  if (nondimensional .and. &
141  (params%valid_path('case.scalar.lambda') .or. &
142  params%valid_path('case.scalar.cp'))) then
143  call neko_error("For non-dimensional setup set the Pe number for&
144  & the scalar")
145  else if (.not. nondimensional .and. &
146  params%valid_path('case.scalar.Pe')) then
147  call neko_error("Dimensional material properties input detected,&
148  & because you set rho and mu for the fluid. &
149  & Please set cp and lambda for the scalar.")
150 
151  ! Non-dimensional case
152  else if (nondimensional) then
153  write(log_buf, '(A)') 'Non-dimensional scalar material properties &
154  & input.'
155  call neko_log%message(log_buf, lvl=neko_log_verbose)
156  write(log_buf, '(A)') 'Specific heat capacity will be set to 1, &
157  & conductivity to 1/Pe.'
158  call neko_log%message(log_buf, lvl=neko_log_verbose)
159 
160  ! Read Pe into lambda for further manipulation.
161  call json_get(params, 'case.scalar.Pe', this%lambda)
162  write(log_buf, '(A,ES13.6)') 'Pe :', this%lambda
163  call neko_log%message(log_buf)
164 
165  ! Set cp and rho to 1 since the setup is non-dimensional.
166  this%cp = 1.0_rp
167  this%rho = 1.0_rp
168  ! Invert the Pe to get conductivity
169  this%lambda = 1.0_rp/this%lambda
170  ! Dimensional case
171  else
172  call json_get(params, 'case.scalar.lambda', this%lambda)
173  call json_get(params, 'case.scalar.cp', this%cp)
174  end if
175  end if
176 
177  call this%write_to_log(.true.)
178 
179  end subroutine material_properties_init
180 
182  subroutine write_to_log(this, scalar)
183  class(material_properties_t), intent(inout) :: this
184  logical, intent(in) :: scalar
185  character(len=LOG_SIZE) :: log_buf
186 
187  write(log_buf, '(A)') 'Set dimensional values:'
188  call neko_log%message(log_buf)
189  write(log_buf, '(A,ES13.6)') 'rho :', this%rho
190  call neko_log%message(log_buf)
191  write(log_buf, '(A,ES13.6)') 'mu :', this%mu
192  call neko_log%message(log_buf)
193  if (scalar) then
194  write(log_buf, '(A,ES13.6)') 'cp :', this%cp
195  call neko_log%message(log_buf)
196  write(log_buf, '(A,ES13.6)') 'lambda :', this%lambda
197  call neko_log%message(log_buf)
198  end if
199  end subroutine write_to_log
200 
201 end module material_properties
Retrieves a parameter by name or throws an error.
Definition: json_utils.f90:44
Abstract interface for setting material properties.
Definition: user_intf.f90:136
Definition: comm.F90:1
integer pe_rank
MPI rank.
Definition: comm.F90:26
Utilities for retrieving parameters from the case files.
Definition: json_utils.f90:34
Logging routines.
Definition: log.f90:34
integer, parameter, public neko_log_verbose
Verbose log level.
Definition: log.f90:67
type(log_t), public neko_log
Global log stream.
Definition: log.f90:61
integer, parameter, public log_size
Definition: log.f90:40
Implements material_properties_t type.
subroutine material_properties_init(this, params, user)
Constructor.
subroutine write_to_log(this, scalar)
Write final dimensional values to the log.
integer, parameter, public rp
Global precision used in computations.
Definition: num_types.f90:12
Interfaces for user interaction with NEKO.
Definition: user_intf.f90:34
subroutine, public dummy_user_material_properties(t, tstep, rho, mu, cp, lambda, params)
Definition: user_intf.f90:352
Utilities.
Definition: utils.f90:35
subroutine neko_warning(warning_msg)
Definition: utils.f90:191
Contains all the material properties necessary in the simulation.