FE-Project
Loading...
Searching...
No Matches
scale_mesh_bndinfo.F90
Go to the documentation of this file.
1!-------------------------------------------------------------------------------
9!-------------------------------------------------------------------------------
10#include "scaleFElib.h"
12 !-----------------------------------------------------------------------------
13 !
14 !++ Used modules
15 !
16 use scale_precision
17 use scale_io
18 use scale_prc
19
20 !-----------------------------------------------------------------------------
21 implicit none
22 private
23 !-----------------------------------------------------------------------------
24 !
25 !++ Public type & procedures
26 !
27
28 type, public :: meshbndinfo
29 integer, allocatable :: list(:)
30 real(rp), allocatable :: val(:)
31 character(len=H_SHORT) :: tag
32 contains
33 procedure :: init => meshbndinfo_init
34 procedure :: final => meshbndinfo_final
35 procedure, private :: set_by_id => meshbndinfo_set_by_id
36 procedure, private :: set_by_name => meshbndinfo_set_by_name
37 generic :: set => set_by_id, set_by_name
38 end type meshbndinfo
39
40 public :: bndtype_nametoid
41
42 !-----------------------------------------------------------------------------
43 !
44 !++ Public parameters & variables
45 !
46 character(len=*), public , parameter :: bnd_type_nospec_name = 'NONSPEC'
47 integer, public, parameter :: bnd_type_nospec_id = 0
48 character(len=*), public, parameter :: bnd_type_periodic_name = 'PERIODIC'
49 integer, public, parameter :: bnd_type_periodic_id = 1
50 character(len=*), public, parameter :: bnd_type_slip_name = 'SLIP'
51 integer, public, parameter :: bnd_type_slip_id = 2
52 character(len=*), public, parameter :: bnd_type_noslip_name = 'NOSLIP'
53 integer, public, parameter:: bnd_type_noslip_id = 3
54 character(len=*), public , parameter :: bnd_type_adiabat_name = 'ADIABATIC'
55 integer, public, parameter :: bnd_type_adiabat_id = 4
56 character(len=*), public , parameter :: bnd_type_fixval_name = 'FIXVAL'
57 integer, public, parameter :: bnd_type_fixval_id = 5
58
59 !-----------------------------------------------------------------------------
60 !
61 !++ Private procedures
62 !
63 !-------------------
64
65contains
66!OCL SERIAL
67 subroutine meshbndinfo_init(this, list_size, tag)
68 use scale_const, only: &
69 undef8 => const_undef8
70 implicit none
71 class(meshbndinfo), intent(inout) :: this
72 integer, intent(in) :: list_size
73 character(*), optional, intent(in) :: tag
74
75 integer :: i
76 !------------------------------------------------------
77
78 allocate( this%list(list_size) )
79 allocate( this%val(list_size) )
80
81 !$omp parallel do
82 do i = 1, list_size
83 this%list(i) = bnd_type_nospec_id
84 this%val(i) = undef8
85 end do
86
87 if (present(tag)) then
88 this%tag = tag
89 else
90 this%tag = ''
91 end if
92
93 return
94 end subroutine meshbndinfo_init
95
96!OCL SERIAL
97 subroutine meshbndinfo_final(this)
98 implicit none
99 class(meshbndinfo), intent(inout) :: this
100 !------------------------------------------------------
101
102 if (allocated(this%list)) deallocate(this%list)
103 if (allocated(this%val)) deallocate(this%val)
104
105 return
106 end subroutine meshbndinfo_final
107
108!OCL SERIAL
109 subroutine meshbndinfo_set_by_id(this, is, ie, bnd_type_id, val)
110 implicit none
111 class(meshbndinfo), intent(inout) :: this
112 integer, intent(in) :: is
113 integer, intent(in) :: ie
114 integer, intent(in) :: bnd_type_id
115 real(rp), intent(in), optional :: val
116 !------------------------------------------------------
117
118 this%list(is:ie) = bnd_type_id
119 if ( present(val) ) then
120 this%val(is:ie) = val
121 end if
122
123 return
124 end subroutine meshbndinfo_set_by_id
125
126!OCL SERIAL
127 subroutine meshbndinfo_set_by_name(this, is, ie, bnd_type_name, val)
128 implicit none
129 class(meshbndinfo), intent(inout) :: this
130 integer, intent(in) :: is
131 integer, intent(in) :: ie
132 character(*), intent(in) :: bnd_type_name
133 real(rp), intent(in), optional :: val
134
135 integer :: bnd_type_id
136 !------------------------------------------------------
137 bnd_type_id = bndtype_nametoid(bnd_type_name)
138 call meshbndinfo_set_by_id(this, is, ie, bnd_type_id, val)
139
140 return
141 end subroutine meshbndinfo_set_by_name
142
143!OCL SERIAL
144 function bndtype_nametoid(bnd_type_name) result(bnd_type_id)
145 implicit none
146 character(*), intent(in) :: bnd_type_name
147
148 integer :: bnd_type_id
149 !------------------------------------------------------
150
151 select case(trim(bnd_type_name))
153 bnd_type_id = bnd_type_nospec_id
155 bnd_type_id = bnd_type_periodic_id
156 case (bnd_type_slip_name)
157 bnd_type_id = bnd_type_slip_id
159 bnd_type_id = bnd_type_noslip_id
161 bnd_type_id = bnd_type_adiabat_id
163 bnd_type_id = bnd_type_fixval_id
164 case default
165 log_error('BndType_NameToID ',*) trim(bnd_type_name) // ' is not supported. Check!'
166 call prc_abort
167 end select
168
169 return
170 end function bndtype_nametoid
171
172end module scale_mesh_bndinfo
module FElib / Mesh / Boundary information
integer, parameter, public bnd_type_slip_id
character(len= *), parameter, public bnd_type_fixval_name
character(len= *), parameter, public bnd_type_slip_name
character(len= *), parameter, public bnd_type_adiabat_name
character(len= *), parameter, public bnd_type_nospec_name
integer, parameter, public bnd_type_fixval_id
integer function, public bndtype_nametoid(bnd_type_name)
integer, parameter, public bnd_type_periodic_id
character(len= *), parameter, public bnd_type_noslip_name
character(len= *), parameter, public bnd_type_periodic_name
integer, parameter, public bnd_type_nospec_id
integer, parameter, public bnd_type_adiabat_id
integer, parameter, public bnd_type_noslip_id