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

Go to the source code of this file.

Functions/Subroutines

subroutine prelecsec4bolt (snstrf, ssecbuf, igrnod, itabm1, flag_r2r, nom_opt, igrbric, lsubmodel)

Function/Subroutine Documentation

◆ prelecsec4bolt()

subroutine prelecsec4bolt ( integer, intent(inout) snstrf,
integer, intent(inout) ssecbuf,
type (group_), dimension(ngrnod) igrnod,
integer, dimension(*), intent(in) itabm1,
integer flag_r2r,
integer, dimension(lnopt1,*) nom_opt,
type (group_), dimension(ngrbric) igrbric,
type(submodel_data), dimension(nsubmod), intent(in) lsubmodel )

Definition at line 42 of file prelecsec4bolt.F.

44C-----------------------------------------------
45C M o d u l e s
46C-----------------------------------------------
47 USE r2r_mod
48 USE message_mod
49 USE groupdef_mod
50 USE submodel_mod
53C-----------------------------------------------
54C I m p l i c i t T y p e s
55C-----------------------------------------------
56#include "implicit_f.inc"
57C-----------------------------------------------
58C C o m m o n B l o c k s
59C-----------------------------------------------
60#include "scr17_c.inc"
61#include "com04_c.inc"
62C-----------------------------------------------
63C D u m m y A r g u m e n t s
64C-----------------------------------------------
65 INTEGER ,INTENT(INOUT) :: SNSTRF,SSECBUF
66 INTEGER ,INTENT(IN) :: ITABM1(*)
67 INTEGER NOM_OPT(LNOPT1,*)
68C-----------------------------------------------
69 TYPE (GROUP_) ,DIMENSION(NGRNOD) :: IGRNOD
70 TYPE (GROUP_) ,DIMENSION(NGRBRIC) :: IGRBRIC
71C-----------------------------------------------
72 TYPE(SUBMODEL_DATA),INTENT(IN) :: LSUBMODEL(NSUBMOD)
73C-----------------------------------------------
74C L o c a l V a r i a b l e s
75C-----------------------------------------------
76 INTEGER I,KK,IBID,ISAV,IGU,IGUS,IGUQ,IGUC,IGUT,IGUP,IGUR,IGUTG,
77 . NNOD,NBINTER,NSEGQ,NSEGS,NSEGC,NSEGT,NSEGP,NSEGR,NSEGTG,NFRAM,
78 . ID,UID,FLAG_FMT,FLAG_FMT_TMP,IFIX_TMP,L,ISTYP,
79 . FLAG_R2R,N1,N2,N3,POS_SEC_R2R,NSEG0,NSEG,
80 . COMPT,NG
81 CHARACTER(LEN=NCHARTITLE)::TITR
82 CHARACTER(LEN=NCHARKEY)::KEY2
83 CHARACTER MESS*40
84 LOGICAL IS_AVAILABLE
85C-----------------------------------------------
86C E x t e r n a l F u n c t i o n s
87C-----------------------------------------------
88 INTEGER GRSIZEN,USR2SYS,GRSIZE_R2R,GRSIZE_ELE
90C=======================================================================
91 flag_fmt = 0
92 nfram = 0
93 snstrf = 30
94 ssecbuf = 20
95 l = 7
96 compt = 0
97 ng = 0
98 igu = 0
99
100 CALL hm_option_start('/SECT')
101
102 DO i=1,nsect
103
104 ng=ng+1
105
106 CALL hm_option_read_key(lsubmodel, option_id=id, option_titr=titr, unit_id=uid, keyword2=key2)
107 nom_opt(1,i)=id
108 CALL fretitl(titr,nom_opt(lnopt1-ltitr+1,i),ltitr)
109
110 CALL hm_get_intv('Axis_Origin_Node_N1', n1, is_available, lsubmodel)
111 CALL hm_get_intv('Axis_Node_N2', n2, is_available, lsubmodel)
112 CALL hm_get_intv('Axis_Node_N3', n3, is_available, lsubmodel)
113 CALL hm_get_intv('ISAVE', isav, is_available, lsubmodel)
114
115 IF(key2(1:5) == 'PARAL' .OR. key2(1:6) == 'CIRCLE') THEN
116 istyp = 1
117 ELSE
118 istyp = 0
119 CALL hm_get_intv('Grnod_ID', igu, is_available, lsubmodel)
120 CALL hm_get_intv('System_Id', nfram, is_available, lsubmodel)
121 ENDIF
122
123 CALL hm_get_intv('grbrick_id', igus, is_available, lsubmodel)
124
125 IF (nfram == 0 .AND. istyp == 0) THEN
126 nnod = grsizen(igu,igrnod,ngrnod)
127 ELSE
128 nnod = 20 * grsize_ele(igus,igrbric,ngrbric)
129 ENDIF
130 nsegs = grsize_ele(igus,igrbric,ngrbric)
131 snstrf = snstrf +30 + nnod !+ NBINTER
132 . + 2*(nsegs) !+NSEGQ+NSEGC+NSEGT+NSEGP+NSEGR+NSEGTG)
133 ssecbuf=ssecbuf+10
134
135 ENDDO
136
137C-----------
138 RETURN
139C-----------
subroutine hm_get_intv(name, ival, is_available, lsubmodel)
subroutine hm_option_start(entity_type)
initmumps id
integer, parameter nchartitle
integer, parameter ncharkey
integer function grsizen(igu, igrnod, grlen)
Definition nintrr.F:497
integer function grsize_ele(igu, igrelem, ngrelem)
Definition nintrr.F:538
integer function grsize_r2r(igu, igrelem, grlen, typ)
subroutine fretitl(titr, iasc, l)
Definition freform.F:620
integer function usr2sys(iu, itabm1, mess, id)
Definition sysfus.F:160