OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
hm_preread_load_pressure.F File Reference
#include "implicit_f.inc"
#include "com04_c.inc"

Go to the source code of this file.

Functions/Subroutines

subroutine hm_preread_load_pressure (numloadp, igrsurf, lsubmodel)

Function/Subroutine Documentation

◆ hm_preread_load_pressure()

subroutine hm_preread_load_pressure ( integer, intent(inout) numloadp,
type (surf_), dimension(nsurf), target igrsurf,
type(submodel_data), dimension(*), intent(in) lsubmodel )

Definition at line 38 of file hm_preread_load_pressure.F.

39C-----------------------------------------------
40C M o d u l e s
41C-----------------------------------------------
42 USE message_mod
43 USE groupdef_mod
44 USE submodel_mod
47C-----------------------------------------------
48C I m p l i c i t T y p e s
49C-----------------------------------------------
50#include "implicit_f.inc"
51C-----------------------------------------------
52C C o m m o n B l o c k s
53C-----------------------------------------------
54#include "com04_c.inc"
55C-----------------------------------------------
56C D u m m y A r g u m e n t s
57C-----------------------------------------------
58 INTEGER,INTENT(INOUT) :: NUMLOADP
59C-----------------------------------------------
60 TYPE (SURF_) ,TARGET, DIMENSION(NSURF) :: IGRSURF
61 TYPE(SUBMODEL_DATA),INTENT(IN)::LSUBMODEL(*)
62C-----------------------------------------------
63C L o c a l V a r i a b l e s
64C-----------------------------------------------
65 INTEGER :: I, ID, NINTERS, IDINT
66 INTEGER :: ISU, IS, J ,NINTERP,NN, NIP
67 CHARACTER(LEN=NCHARTITLE) :: TITR
68 LOGICAL IS_AVAILABLE
69C-----------------------------------------------
70C S o u r c e L i n e s
71C-----------------------------------------------
72 is_available = .false.
73C--------------------------------------------------
74C START BROWSING MODEL /LOAD/PRESSURE
75C--------------------------------------------------
76 CALL hm_option_start('/LOAD/PRESSURE')
77C-----------------------------------------------
78 DO i=1,nloadp_hyd
79C--------------------------------------------------
80C EXTRACT DATAS OF /LOAD/PRESSURE... LINE
81C--------------------------------------------------
82 CALL hm_option_read_key(lsubmodel,
83 . option_id = id,
84 . option_titr = titr)
85C--------------------------------------------------
86C EXTRACT DATAS (INTEGER VALUES)
87C--------------------------------------------------
88 CALL hm_get_intv ('surf_ID',isu,is_available,lsubmodel)
89C EXTRACT DATAS (INTEGER VALUES) : Number of interfaces
90 CALL hm_get_intv('N_inter_P',ninterp,is_available,lsubmodel)
91 ninters = 0
92 IF(ninterp > 0) THEN
93 DO nip=1,ninterp
94
95C EXTRACT DATAS (INTEGER VALUES)
96
97 CALL hm_get_int_array_index('Inter_IDs',idint,nip,is_available,lsubmodel)
98
99 IF(idint > 0 ) ninters = ninters + 1
100 ENDDO
101 ENDIF
102
103C-------
104 is = 0
105 DO j=1,nsurf
106 IF(isu==igrsurf(j)%ID)is=j
107 ENDDO
108 IF(is == 0)THEN
109 CALL ancmsg(msgid=931,
110 . msgtype=msgerror,
111 . anmode=aninfo_blind_1,
112 . i1=id,
113 . c1=titr,
114 . i2=isu)
115 ENDIF
116C-----------
117 numloadp = numloadp + 4*igrsurf(is)%NSEG
118 nintloadp = nintloadp + ninters
119 ENDDO
120C-----------------------------------------------
121 RETURN
subroutine hm_get_int_array_index(name, ival, index, is_available, lsubmodel)
subroutine hm_get_intv(name, ival, is_available, lsubmodel)
subroutine hm_option_start(entity_type)
initmumps id
integer, parameter nchartitle
subroutine ninterp(ifunc, npc, pld, npoint, xv, yv)
Definition ninterp.F:32
subroutine ancmsg(msgid, msgtype, anmode, i1, i2, i3, i4, i5, i6, i7, i8, i9, i10, i11, i12, i13, i14, i15, i16, i17, i18, i19, i20, r1, r2, r3, r4, r5, r6, r7, r8, r9, c1, c2, c3, c4, c5, c6, c7, c8, c9, prmode)
Definition message.F:889