OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
lce16q.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!|| lce16q3 ../starter/source/elements/solid_2d/quad/lce16q.F
25!||--- called by ------------------------------------------------------
26!|| lectur ../starter/source/starter/lectur.F
27!||--- calls -----------------------------------------------------
28!|| reordr ../starter/source/elements/solid_2d/quad/reordr.f
29!|| usr2sys ../starter/source/system/sysfus.F
30!||--- uses -----------------------------------------------------
31!||====================================================================
32 SUBROUTINE lce16q3(IXQ ,ISEL ,PM ,IPOINT ,ITAB ,ITABM1,
33 . ICODE ,IPARTQ,IGRQUAD,IPM ,IGEO )
34C--------------------------------------------------------
35C LECTURE DES ELEMENTS 2D
36C VERSION NUMEROTATION DES NOEUDS LIBRE/MARS 90/DIM
37C LECTURE FORMAT IDENTIQUE AUX COQUES
38C-----------------------------------------------
39C M o d u l e s
40C-----------------------------------------------
41 USE groupdef_mod
42C-----------------------------------------------
43C I m p l i c i t T y p e s
44C-----------------------------------------------
45#include "implicit_f.inc"
46C-----------------------------------------------
47C C o m m o n B l o c k s
48C-----------------------------------------------
49#include "com04_c.inc"
50#include "units_c.inc"
51#include "scr03_c.inc"
52#include "param_c.inc"
53#include "titr_c.inc"
54C-----------------------------------------------
55C D u m m y A r g u m e n t s
56C-----------------------------------------------
57 INTEGER IXQ(NIXQ,NUMELQ), ISEL(*), IPOINT(2,*), ITAB(*),
58 . itabm1(*), icode(*),ipartq(*),
59 . ipm(npropmi,nummat),igeo(npropgi,numgeo)
60 my_real pm(npropm,nummat)
61C-----------------------------------------------
62 TYPE (GROUP_) ,DIMENSION(NGRQUAD) :: IGRQUAD
63C-----------------------------------------------
64C L o c a l V a r i a b l e s
65C-----------------------------------------------
66 INTEGER I, J, MT, MLAW, JTUR, ICODT, I1, I2, INEW
67 INTEGER IC,IC1,IC2,IC3,IC4,MID,PID
68 CHARACTER MESS*40, MESS2*40
69C-----------------------------------------------
70C E x t e r n a l F u n c t i o n s
71C-----------------------------------------------
72 INTEGER USR2SYS
73 DATA mess/'2D SOLID ELEMENTS DEFINITION '/
74 DATA mess2/'2D SOLID ELEMENTS SELECTION FOR TH PLOT '/
75C
76C----------------------------------------------------
77C DETECTION DES ELEMENTS LOIS 6 PAROI---->LOI 17
78C----------------------------------------------------
79C LOI 17 SI LA BCS EST 011 OU 111
80 DO i=1,numelq
81 mt=ixq(1,i)
82 mlaw=nint(pm(19,mt))
83 jtur=nint(pm(70,mt))
84 DO j=2,5
85 IF((mlaw==6.AND.jtur/=0) .OR. mlaw==46)THEN
86 ic=icode(ixq(j,i))
87 ic1=ic/512
88 ic2=(ic-512*ic1)/64
89 ic3=(ic-512*ic1-64*ic2)/8
90 ic4=(ic-512*ic1-64*ic2-8*ic3)
91 IF(ic1==3.OR.ic1==7.OR.ic4==3.OR.ic4==7)
92 . ixq(1,i)=-iabs(ixq(1,i))
93 ENDIF
94 ENDDO
95 ENDDO
96C----------------------------------------------------
97C CLASSEMENT DES ELEMENTS PAR LOI DE MATERIAU
98C----------------------------------------------------
99 CALL reordr(ixq ,nixq ,numelq ,pm ,ipoint ,
100 . ipartq,ngrquad,igrquad,nummat)
101C
102 i1=1
103 i2=min0(50,numelq)
104C
105 IF(ipri>=5)THEN
106 WRITE (iout,'(//A//)') titre(206)
107 90 WRITE (iout,'(//A/A//A/)')titre(100),titre(101),titre(102)
108 DO 100 i=i1,i2
109 inew=ipoint(1,i)
110 IF(inew < 1)cycle
111 IF(ixq(1,inew)<1)cycle
112 mid =ipm(1,ixq(1,inew))
113 pid =igeo(1,ixq(6,inew))
114 100 WRITE (iout,'(8I10)')ixq(nixq,inew),inew,mid,pid,(itab(ixq(j,inew)),j=2,5)
115 IF(i2==numelq)GOTO 200
116 i1=i1+50
117 i2=min0(i2+50,numelq)
118 GOTO 90
119 ENDIF
120C
121 200 CONTINUE
122C
123 RETURN
124 END
#define my_real
Definition cppsort.cpp:32
subroutine lce16q3(ixq, isel, pm, ipoint, itab, itabm1, icode, ipartq, igrquad, ipm, igeo)
Definition lce16q.F:34
subroutine reordr(ix, nx, nel, pm, ipoint, iparts, ngrele, igrelem, nummat)
Definition reordr.F:31
program starter
Definition starter.F:39