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

Go to the source code of this file.

Functions/Subroutines

subroutine hm_preread_impvel (nimpvel, igrnod, ipart, ipartr, nfvlag, unitab, lsubmodel)

Function/Subroutine Documentation

◆ hm_preread_impvel()

subroutine hm_preread_impvel ( integer, intent(out) nimpvel,
type (group_), dimension(ngrnod), intent(in) igrnod,
integer, dimension(lipart1,*) ipart,
integer, dimension(*) ipartr,
integer, intent(inout) nfvlag,
type(unit_type_), intent(in) unitab,
type(submodel_data), dimension(*), intent(in) lsubmodel )

Definition at line 39 of file hm_preread_impvel.F.

42C============================================================================
43C M o d u l e s
44C-----------------------------------------------
45 USE message_mod
46 USE groupdef_mod
47 USE submodel_mod
49 USE unitab_mod
51C-----------------------------------------------
52C I m p l i c i t T y p e s
53C-----------------------------------------------
54#include "implicit_f.inc"
55C-----------------------------------------------
56C C o m m o n B l o c k s
57C-----------------------------------------------
58#include "com04_c.inc"
59#include "scr17_c.inc"
60C-----------------------------------------------
61C D u m m y A r g u m e n t s
62C-----------------------------------------------
63 INTEGER ,INTENT(OUT) :: NIMPVEL
64 INTEGER ,INTENT(INOUT) :: NFVLAG
65 INTEGER IPART(LIPART1,*), IPARTR(*)
66 TYPE(UNIT_TYPE_), INTENT(IN) :: UNITAB
67 TYPE (GROUP_) , DIMENSION(NGRNOD) ,INTENT(IN) :: IGRNOD
68 TYPE(SUBMODEL_DATA), DIMENSION(*) ,INTENT(IN) :: LSUBMODEL
69C-----------------------------------------------
70C L o c a l V a r i a b l e s
71C-----------------------------------------------
72 INTEGER :: I,N,OPTID,NFVEL,NFGEO,IGS,GRNOD_ID,PART_ID,NNOD,JPART,SYS_TYPE
73 CHARACTER(LEN=NCHARKEY) :: KEY
74 CHARACTER(LEN=NCHARTITLE) :: TITR
75 LOGICAL :: IS_AVAILABLE
76C-----------------------------------------------
77C E x t e r n a l F u n c t i o n s
78C-----------------------------------------------
79 INTEGER NGR2USRN
80c--------------------------------------------------
81c Count number of nodes with imposed velocity => NUMVEL
82C======================================================================|
83 is_available = .false.
84c
85 nimpvel = 0 ! initialize counter of nodes
86c--------------------------------------------------
87c /IMPVEL and /IMPVEL/LAGMUL
88c--------------------------------------------------
89 CALL hm_option_count('/impvel',NFVEL)
90c
91 CALL HM_OPTION_START('/impvel')
92c
93 DO I=1,NFVEL
94c
95 CALL HM_OPTION_READ_KEY(LSUBMODEL,
96 . OPTION_ID = OPTID,
97 . OPTION_TITR = TITR,
98 . KEYWORD2 = KEY)
99c
100 IF (KEY(1:4) /= 'fgeo') THEN
101 CALL HM_GET_INTV('rad_system_input_type' ,SYS_TYPE ,IS_AVAILABLE,LSUBMODEL)
102 CALL HM_GET_INTV('entityid' ,GRNOD_ID ,IS_AVAILABLE,LSUBMODEL)
103 IGS = NGR2USRN(GRNOD_ID,IGRNOD,NGRNOD,NNOD)
104 IF (IGS > 0) THEN
105 NIMPVEL = NIMPVEL + NNOD
106 IF (KEY(1:6) == 'lagmul') NFVLAG = NFVLAG + NNOD
107 END IF
108 ENDIF
109c
110 ENDDO ! DO I=1,NFVEL
111c--------------------------
112c /IMPVEL/FGEO
113c--------------------------
114 CALL HM_OPTION_COUNT('/impvel/fgeo',NFGEO)
115c
116 CALL HM_OPTION_START('/impvel/fgeo')
117c
118
119 DO I=1,NFGEO
120c
121 CALL HM_OPTION_READ_KEY(LSUBMODEL,
122 . OPTION_ID = OPTID,
123 . OPTION_TITR = TITR,
124 . KEYWORD2 = KEY)
125 IF (KEY(1:4) == 'fgeo') THEN
126 CALL HM_GET_INTV('rad_spring_part' ,PART_ID ,IS_AVAILABLE,LSUBMODEL)
127 IF (PART_ID > 0) THEN
128 JPART = 0
129 DO N=1,NPART
130 IF (IPART(4,N) == PART_ID) JPART = N
131 ENDDO
132 IF (JPART == 0) THEN
133 CALL ANCMSG(MSGID=1077, MSGTYPE=MSGERROR,
134 . ANMODE=ANINFO,
135 . I1=OPTID,
136 . C1=TITR,
137 . I2=PART_ID)
138 ENDIF
139 DO N=1,NUMELR
140 IF (IPARTR(N) == JPART) NIMPVEL = NIMPVEL + 1
141 ENDDO
142 ENDIF
143c
144 CALL HM_GET_INTV('distribution_table_count' ,NNOD ,IS_AVAILABLE,LSUBMODEL)
145 NIMPVEL = NIMPVEL + NNOD
146 ENDIF
147 ENDDO ! DO I=1,NFGEO
148c-----------
149 RETURN
subroutine hm_option_count(entity_type, hm_option_number)
integer, parameter nchartitle
integer, parameter ncharkey