OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
alefvm_init.F
Go to the documentation of this file.
1Copyright> OpenRadioss
2Copyright> Copyright (C) 1986-2025 Altair Engineering Inc.
3Copyright>
4Copyright> This program is free software: you can redistribute it and/or modify
5Copyright> it under the terms of the GNU Affero General Public License as published by
6Copyright> the Free Software Foundation, either version 3 of the License, or
7Copyright> (at your option) any later version.
8Copyright>
9Copyright> This program is distributed in the hope that it will be useful,
10Copyright> but WITHOUT ANY WARRANTY; without even the implied warranty of
11Copyright> MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
12Copyright> GNU Affero General Public License for more details.
13Copyright>
14Copyright> You should have received a copy of the GNU Affero General Public License
15Copyright> along with this program. If not, see <https://www.gnu.org/licenses/>.
16Copyright>
17Copyright>
18Copyright> Commercial Alternative: Altair Radioss Software
19Copyright>
20Copyright> As an alternative to this open-source version, Altair also offers Altair Radioss
21Copyright> software under a commercial license. Contact Altair to discuss further if the
22Copyright> commercial version may interest you: https://www.altair.com/radioss/.
23!||====================================================================
24!|| alefvm_init ../engine/source/ale/alefvm/alefvm_init.F
25!||--- called by ------------------------------------------------------
26!|| restalloc ../engine/source/output/restart/arralloc.F
27!||--- uses -----------------------------------------------------
28!|| alefvm_mod ../common_source/modules/ale/alefvm_mod.F
29!||====================================================================
30 SUBROUTINE alefvm_init()
31C-----------------------------------------------
32C D e s c r i p t i o n
33C-----------------------------------------------
34C 'alefvm' is related to a collocated scheme (built from FVM and based on Godunov scheme)
35C which was temporarily introduced for experimental option /INTER/TYPE22 (FSI coupling with cut cell method)
36C This cut cell method is not completed, abandoned, and is not an official option.
37C There is no other use for this scheme which is automatically enabled when /INTER/TYPE22 is defined (INT22>0 => IALEFVM=1).
38C
39C This subroutine is treating an uncut cell.
40C-----------------------------------------------
41C M o d u l e s
42C-----------------------------------------------
43 USE alefvm_mod , only:alefvm_param
44C-----------------------------------------------
45C I m p l i c i t T y p e s
46C-----------------------------------------------
47#include "implicit_f.inc"
48C-----------------------------------------------
49C L o c a l V a r i a b l e s
50C-----------------------------------------------
51 TYPE ptrarray
52 INTEGER, POINTER :: ptr
53 END TYPE
54
55 TYPE(ptrARRAY),ALLOCATABLE,DIMENSION(:) :: FLAG
56
57 INTEGER :: NVAR, I
58C-----------------------------------------------
59C D e s c r i p t i o n
60C-----------------------------------------------
61C This subroutine initializes parameter for
62C full FVM formulation. Especially output options.
63C-----------------------------------------------
64C P r e - C o n d i t i o n s
65C-----------------------------------------------
66 IF(alefvm_param%IEnabled == 0) RETURN
67C-----------------------------------------------
68C S o u r c e L i n e s
69C-----------------------------------------------
70
71 ALLOCATE(flag(32))
72 nvar = 0
73
74 !----------------------------!
75 ! ALL OUTPUTS !
76 ! 0: all off !
77 ! 1: all according below !
78 !----------------------------!
79 alefvm_param%IOUTP = 0
80 !----------------------------!
81 ! SPECIFIC OUTPUTS !
82 ! 0 OFF !
83 ! -1 all elem in group !
84 ! >0 only given user id !
85 !----------------------------!
86 alefvm_param%IOUTP_GRAV = 0 ; nvar=nvar+1; flag(nvar)%ptr => alefvm_param%IOUTP_GRAV
87 alefvm_param%IOUTP_STRESS = -0 ; nvar=nvar+1; flag(nvar)%ptr => alefvm_param%IOUTP_STRESS
88 alefvm_param%IOUTP_FINT = -0 ; nvar=nvar+1; flag(nvar)%ptr => alefvm_param%IOUTP_FINT
89 alefvm_param%IOUTP_FLUX = -0 ; nvar=nvar+1; flag(nvar)%ptr => alefvm_param%IOUTP_FLUX
90 alefvm_param%IOUTP_CONV = -0 ; nvar=nvar+1; flag(nvar)%ptr => alefvm_param%IOUTP_CONV
91 alefvm_param%IOUTP_EPSDOT = 0 ; nvar=nvar+1; flag(nvar)%ptr => alefvm_param%IOUTP_EPSDOT
92 alefvm_param%IOUTP_SCHEME = -1 ; nvar=nvar+1; flag(nvar)%ptr => alefvm_param%IOUTP_SCHEME
93 alefvm_param%IOUTP_BCS = 0 ; nvar=nvar+1; flag(nvar)%ptr => alefvm_param%IOUTP_BCS
94 alefvm_param%IOUTP_WFEXT = 0 ; nvar=nvar+1; flag(nvar)%ptr => alefvm_param%IOUTP_WFEXT
95
96 DO i=1,nvar
97 flag(i)%ptr =flag(i)%ptr * alefvm_param%IOUTP
98 ENDDO
99
100 !----------------------------!
101 ! FVM FORMULATION !
102 ! IFORM=2 Mom. Weighted !
103 ! IFORM=3 Roe-averaged !
104 ! IFORM=4 Centered ! obsolete
105 ! IFORM=5 Interpolated ! obsolete
106 !----------------------------!
107 alefvm_param%IFORM = 0 ; !Now set through control card /EULER/MAT or /ALE/MAT
108
109 !----------------------------!
110 ! FVM FORMULATION !
111 ! IFORM =0 +0*WFEXT !
112 ! IFORM =1 +1*WFEXT !
113 !----------------------------!
114 alefvm_param%IWFEXT = 0 ;
115 !----------------------------!
116
117
118
119
120C-----------------------------------------------
121 RETURN
122 END
subroutine alefvm_init()
Definition alefvm_init.F:31
type(alefvm_param_), target alefvm_param
Definition alefvm_mod.F:121