Télécharger hhoprm.eso

Retour à la liste

Numérotation des lignes :

hhoprm
  1. C HHOPRM SOURCE OF166741 24/05/06 21:15:14 11082
  2. C HHOPRM SOURCE
  3.  
  4. SUBROUTINE HHOPRM (charHHO, modlHHO, nobHHO, lentHHO, iret)
  5.  
  6. IMPLICIT INTEGER(I-N)
  7. IMPLICIT REAL*8(A-H,O-Z)
  8.  
  9. -INC PPARAM
  10. -INC CCOPTIO
  11. -INC CCGEOME
  12.  
  13. -INC CCHHOPA
  14. -INC CCHHOPR
  15.  
  16. -INC SMMODEL
  17. -INC SMELEME
  18. -INC SMLENTI
  19. -INC SMLREEL
  20.  
  21. EXTERNAL LONG
  22.  
  23. CHARACTER*(*) charHHO
  24.  
  25. CHARACTER*(6) nomsg
  26. CHARACTER*(LOCHAI) charerr
  27.  
  28. iret = 0
  29.  
  30. C= La chaine charHHO est de la forme : "hho_cc_ff_hyp" (suite a HHOPRE)
  31. n_c = LONG(charHHO)
  32. c-dbg write(ioimp,*) 'HHOPRM =',charHHO(1:n_c)
  33.  
  34. imodel = modlHHO
  35. c* segact,imodel*nomod (segment actif en entree)
  36.  
  37. mlent2 = lentHHO
  38. c* segact,mlent2*nomod (segment actif en entree)
  39.  
  40. mailHHO = imodel.IMAMOD
  41. meleme = mailHHO
  42. c* segact,meleme*nomod (segment actif en entree)
  43.  
  44. ity = meleme.ITYPEL
  45. nbnoe = meleme.NUM(/1)
  46. c* pour l'instant poly03->tri3 et poly04->qua4
  47. ityl = ity
  48. IF (ity.EQ.32) THEN
  49. if (nbnoe.eq.3) ityl = 4
  50. if (nbnoe.eq.4) ityl = 8
  51. END IF
  52. nomsg = ' '
  53. CALL CHCASS(NOMS(ityl),0,nomsg(1:4))
  54. IF (ityl.EQ.32) THEN
  55. WRITE(nomsg(5:6),'(I2.2)') nbnoe
  56. END IF
  57. n_s = LONG(nomsg)
  58. c-dbg write(ioimp,*) 'HHOPRM =',nomsg(1:n_s),'=',nbnoe,ity,ityl
  59.  
  60. JG = 20+NFHMAX
  61. SEGINI,mlenti
  62. DO i = 1, JG
  63. mlenti.lect(i) = -999
  64. END DO
  65. ile = JG
  66.  
  67. mlenti.lect( 1) = mlent2.lect(1)
  68. mlenti.lect( 2) = mlent2.lect(2)
  69. mlenti.lect( 3) = mlent2.lect(3)
  70. mlenti.lect( 4) = mlent2.lect(4)
  71. mlenti.lect( 5) = mlent2.lect(5)
  72. mlenti.lect( 6) = nbnoe
  73. mlenti.lect( 7) = nbnoe
  74.  
  75. C= Tableau de flottants : inutilise ici
  76. JG = 1
  77. SEGINI,mlreel
  78. ilr = JG
  79.  
  80. iretc = 0
  81. C= On complete le tableau mlenti.LECT
  82. CALL HHOC3M('INIT',charHHO(1:n_c)//'_'//nomsg(1:n_s),
  83. & mlenti.lect,ile, mlreel.prog,ilr,
  84. & iretc,charerr)
  85.  
  86. C= Suppression du tableau de flottants
  87. SEGSUP,MLREEL
  88.  
  89. C= Erreur dans HHOC3M : A affiner
  90. IF (iretc.NE.0) THEN
  91. write(ioimp,*) 'HHO -> HHOPRM - ERROR ='
  92. write(ioimp,*) charerr(1:LONG(charerr))
  93. iret = 21
  94. return
  95. END IF
  96.  
  97. c-dbg write(ioimp,*) 'RETOUR de HHOC3M-INIT'
  98. c-dbg write(ioimp,*) (mlenti.lect(i),i=1,20)
  99.  
  100. c-dbg mlenti.lect( 8) = 3*nbnoe
  101. c-dbg mlenti.lect( 9) = IDIM
  102. c-dbg mlenti.lect(10) = 9
  103. c-dbg mlenti.lect(11) = mlenti.lect( 9) *
  104. c-dbg & ( mlenti.lect( 5) + mlenti.lect( 7) * mlenti.lect( 3) )
  105. c-dbg mlenti.lect(12) = mlenti.lect( 9) *
  106. c-dbg & ( mlenti.lect( 7) * mlenti.lect( 3) )
  107. c-dbg mlenti.lect(13) = mlenti.lect( 9) * mlenti.lect( 5)
  108. c-dbg mlenti.lect(14) = 9 * mlenti.lect(11)
  109. c-dbg mlenti.lect(15) = mlenti.lect(14) * mlenti.lect( 8)
  110. c-dbg mlenti.lect(16) = mlenti.lect(11) * mlenti.lect(11)
  111. c-dbg mlenti.lect(17) = mlenti.lect(13) * mlenti.lect(13)
  112. c-dbg mlenti.lect(18) = mlenti.lect(13) * mlenti.lect(12)
  113. c-dbg mlenti.lect(19) = mlenti.lect(13)
  114. c-dbgccccc mentli.lect(20+1:20+d % num_faces) = d % num_vertices_per_face(1:d%num_faces)
  115.  
  116. C= On recherche les faces du maillage dans sa totalite :
  117. CALL ECROBJ('MAILLAGE',mailHHO)
  118. IF (IDIM.EQ.2) THEN
  119. CALL CHANLG
  120. ELSE
  121. CALL ECRCHA('NOID')
  122. CALL ENVVO2(1)
  123. END IF
  124. CALL LIROBJ('MAILLAGE',mailSQE,1,iretc)
  125. IF (IERR.NE.0) THEN
  126. iret = 21
  127. RETURN
  128. END IF
  129.  
  130. CALL ACTOBJ('MAILLAGE',mailHHO,1)
  131. CALL HHOLIM('CELL',mailHHO,lentHHO,iret)
  132. IF (iret.NE.0) RETURN
  133.  
  134. CALL ACTOBJ('MAILLAGE',mailHHO,1)
  135. CALL HHOLIM('FAEL',mailHHO,lentHHO,iret)
  136. IF (iret.NE.0) RETURN
  137.  
  138. CALL ACTOBJ('MAILLAGE',mailSQE,1)
  139. CALL HHOLIM('FACE',mailSQE,lentHHO,iret)
  140. IF (iret.NE.0) RETURN
  141.  
  142. C= Pour memoire mlent2 = lentHHO
  143.  
  144. C= On stocke dans le IMODEL le nombre de ddls par face et par cellule
  145. C= Pour eviter souci dans ACTOBJ : entier < ou = 0 !
  146. imodel.INFMOD( 9) = -1 * mlenti.lect(3)
  147. imodel.INFMOD(12) = -1 * mlenti.lect(5)
  148.  
  149. C= Chaine pour les informations HHO
  150. CALL POSCHA(charHHO(1:n_c)//'_'//nomsg(1:n_s),I_POS)
  151. imodel.TYMODE(nobHHO+1) = 'MOT '
  152. imodel.IVAMOD(nobHHO+1) = I_POS
  153.  
  154. C= Le tableau des donnees de mlenti :
  155. imodel.TYMODE(nobHHO+2) = 'LISTENTI'
  156. imodel.IVAMOD(nobHHO+2) = mlenti
  157.  
  158. C Liste entiers de chaque arete de la zone
  159. imodel.TYMODE(nobHHO+3) = 'LISTENTI'
  160. imodel.IVAMOD(nobHHO+3) = mlent2.lect(8)
  161.  
  162. C Liste entiers donnant les aretes pour chaque cellule de la zone
  163. imodel.TYMODE(nobHHO+4) = 'LISTENTI'
  164. imodel.IVAMOD(nobHHO+4) = mlent2.lect(9)
  165.  
  166. C Liste entiers donnant les cellules de la zone
  167. imodel.TYMODE(nobHHO+5) = 'LISTENTI'
  168. imodel.IVAMOD(nobHHO+5) = mlent2.lect(10)
  169.  
  170. c-dbgC Construction du maillage des points supports :
  171. c-dbg mlent3 = mlent2.lect(8)
  172. c-dbg CALL HHOMPO('FACE',mlent3,ipt3)
  173. c-dbg imodel.TYMODE(nobHHO+6) = 'MAILLAGE'
  174. c-dbg imodel.IVAMOD(nobHHO+6) = ipt3
  175. c-dbg
  176. c-dbgC Maillage des points supports :
  177. c-dbg mlent3 = mlent2.lect(10)
  178. c-dbg CALL HHOMPO('CELL',mlent3,ipt3)
  179. c-dbg imodel.TYMODE(nobHHO+7) = 'MAILLAGE'
  180. c-dbg imodel.IVAMOD(nobHHO+7) = ipt3
  181.  
  182. c RETURN
  183. END
  184.  
  185.  
  186.  

© Cast3M 2003 - Tous droits réservés.
Mentions légales