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

Go to the source code of this file.

Functions/Subroutines

subroutine iniboltprel (ixs, ipreload, preload, vpreload, iflag_bpreload)

Function/Subroutine Documentation

◆ iniboltprel()

subroutine iniboltprel ( integer, dimension(nixs,*) ixs,
integer, dimension(3,*) ipreload,
preload,
vpreload,
integer, dimension(*) iflag_bpreload )

Definition at line 33 of file iniboltprel.F.

34C-----------------------------------------------
35C M o d u l e s
36C-----------------------------------------------
37! USE R2R_MOD
38 USE message_mod
39C-----------------------------------------------
40C I m p l i c i t T y p e s
41C-----------------------------------------------
42#include "implicit_f.inc"
43C-----------------------------------------------
44C C o m m o n B l o c k s
45C-----------------------------------------------
46#include "com04_c.inc"
47#include "boltpr_c.inc"
48C-----------------------------------------------
49C D u m m y A r g u m e n t s
50C-----------------------------------------------
51 INTEGER IXS(NIXS,*), IPRELOAD(3,*), IFLAG_BPRELOAD(*)
53 . preload(6,*), vpreload(7,*)
54C-----------------------------------------------
55C L o c a l V a r i a b l e s
56C-----------------------------------------------
57 INTEGER IE, STAT, IPL, NE, J
58 INTEGER WORKS(70000)
59 INTEGER, DIMENSION(:), ALLOCATABLE ::ITRIS
60 INTEGER, DIMENSION(:), ALLOCATABLE ::INDEXS
61 INTEGER, DIMENSION(:), ALLOCATABLE ::KSYSUSRS
62C-----------------------------------------------
63C E x t e r n a l F u n c t i o n s
64C-----------------------------------------------
65 INTEGER UEL2SYS
66 EXTERNAL uel2sys
67C=======================================================================
68 ALLOCATE (itris(numels) ,stat=stat)
69 IF (stat /= 0) THEN
70 CALL ancmsg(msgid=268,anmode=aninfo,
71 . msgtype=msgerror,
72 . c1='ITRIS')
73 RETURN
74 END IF
75 ALLOCATE (indexs(2*numels) ,stat=stat)
76 IF (stat /= 0) THEN
77 CALL ancmsg(msgid=268,anmode=aninfo,
78 . msgtype=msgerror,
79 . c1='INDEXS')
80 RETURN
81 END IF
82 ALLOCATE (ksysusrs(2*numels),stat=stat)
83 IF (stat /= 0) THEN
84 CALL ancmsg(msgid=268,anmode=aninfo,
85 . msgtype=msgerror,
86 . c1='KSYSUSRS')
87 RETURN
88 END IF
89 itris = 0
90 indexs = 0
91 ksysusrs = 0
92c
93 vpreload(1:6,1:numels) = zero
94c
95 DO ie = 1, numels
96 itris(ie) = ixs(nixs,ie)
97 END DO
98 CALL my_orders(0,works,itris,indexs,numels,1)
99 DO j = 1, numels
100 ie=indexs(j)
101 ksysusrs(j) =ixs(nixs,ie)
102 ksysusrs(numels+j)=ie
103 END DO
104c
105 DO ipl = 1,numpreload
106 ne = ipreload(3,ipl)
107C No systeme dans le D00, de l'elt:
108 ie=uel2sys(ne,ksysusrs,numels)
109 IF(ie/=0)THEN
110 vpreload(1,ie) = preload(1,ipl)
111 vpreload(2,ie) = preload(2,ipl)
112 vpreload(3,ie) = preload(3,ipl)
113 vpreload(4,ie) = preload(4,ipl)
114 vpreload(5,ie) = preload(5,ipl)
115 vpreload(6,ie) = preload(6,ipl)
116 vpreload(7,ie) = ipreload(2,ipl)
117 ENDIF
118 ENDDO
119!::: Creer l'equivalent de ptsol pour le BPREL
120 DO ie=1,numels
121 ne = ixs(nixs,ie)
122 j=uel2sys(ne,ksysusrs,numels)
123 iflag_bpreload(ie) =j
124 END DO
125!:::
126C-----------
127 DEALLOCATE(ksysusrs,indexs,itris)
128 RETURN
#define my_real
Definition cppsort.cpp:32
void my_orders(int *mode, int *iwork, int *data, int *index, int *n, int *irecl)
Definition my_orders.c:82
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
integer function uel2sys(iu, ksysusr, numel)
Definition yctrl.F:408