~ubuntu-branches/ubuntu/precise/code-saturne/precise

« back to all changes in this revision

Viewing changes to src/lagr/memla2.f90

  • Committer: Package Import Robot
  • Author(s): Sylvestre Ledru
  • Date: 2011-11-24 00:00:08 UTC
  • mfrom: (6.1.9 sid)
  • Revision ID: package-import@ubuntu.com-20111124000008-2vo99e38267942q5
Tags: 2.1.0-3
Install a missing file

Show diffs side-by-side

added added

removed removed

Lines of Context:
1
 
!-------------------------------------------------------------------------------
2
 
 
3
 
!     This file is part of the Code_Saturne Kernel, element of the
4
 
!     Code_Saturne CFD tool.
5
 
 
6
 
!     Copyright (C) 1998-2009 EDF S.A., France
7
 
 
8
 
!     contact: saturne-support@edf.fr
9
 
 
10
 
!     The Code_Saturne Kernel is free software; you can redistribute it
11
 
!     and/or modify it under the terms of the GNU General Public License
12
 
!     as published by the Free Software Foundation; either version 2 of
13
 
!     the License, or (at your option) any later version.
14
 
 
15
 
!     The Code_Saturne Kernel is distributed in the hope that it will be
16
 
!     useful, but WITHOUT ANY WARRANTY; without even the implied warranty
17
 
!     of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
18
 
!     GNU General Public License for more details.
19
 
 
20
 
!     You should have received a copy of the GNU General Public License
21
 
!     along with the Code_Saturne Kernel; if not, write to the
22
 
!     Free Software Foundation, Inc.,
23
 
!     51 Franklin St, Fifth Floor,
24
 
!     Boston, MA  02110-1301  USA
25
 
 
26
 
!-------------------------------------------------------------------------------
27
 
 
28
 
subroutine memla2 &
29
 
!================
30
 
 
31
 
 ( idbia0 , idbra0 ,                                              &
32
 
   nfabor , ncelet , nfac   ,                                     &
33
 
   nbpmax , nvp    , nvp1   , nvep   , nivep  ,                   &
34
 
   iindep , iibord , iettpa , iauxl  , iauxl2 ,                   &
35
 
   itaup  , iitlag , ipiil  ,                                     &
36
 
   ivagau , itsuf  , itsup  , ibx    ,                            &
37
 
   igradp , igradv , icroul ,                                     &
38
 
   itepct , itsfex , itsvar ,                                     &
39
 
   icpgd1 , icpgd2 , icpght ,                                     &
40
 
   ibrgau , itebru ,                                              &
41
 
   iw1    , iw2    , iw3    ,                                     &
42
 
   ifinia , ifinra )
43
 
 
44
 
 
45
 
!===============================================================================
46
 
!  FONCTION
47
 
!  --------
48
 
 
49
 
!   SOUS-PROGRAMME DU MODULE LAGRANGIEN :
50
 
!   -------------------------------------
51
 
 
52
 
! Reservation de la memoire pour les tableaux qui ne doivent pas
53
 
! etre conserves en dehors de la boucle en temps.
54
 
 
55
 
!-------------------------------------------------------------------------------
56
 
! Arguments
57
 
!__________________.____._____.________________________________________________.
58
 
! name             !type!mode ! role                                           !
59
 
!__________________!____!_____!________________________________________________!
60
 
! idbia0/idbra0    ! tr ! <-- ! pointeur de la premiere cas libre des          !
61
 
! nfabor           ! i  ! <-- ! number of boundary faces                       !
62
 
! ncelet           ! e  ! <-- ! nombre d'elements                              !
63
 
! nfac             ! i  ! <-- ! number of interior faces                       !
64
 
! nbpmax           ! e  ! <-- ! nombre max de particulies autorise             !
65
 
! nvp              ! e  ! <-- ! nombre de variables particulaires              !
66
 
! nvp1             ! e  ! <-- ! nvp sans position, vfluide, vpart              !
67
 
! nvep             ! e  ! <-- ! nombre info particulaires (reels)              !
68
 
! nivep            ! e  ! <-- ! nombre info particulaires (entiers)            !
69
 
! iindep           ! e  ! --> ! pointeur sur indep (num cel de depart          !
70
 
! iibord           ! e  ! --> ! pointeur sur ibord                             !
71
 
! iettpa           ! e  ! --> ! pointeur sur ettpa                             !
72
 
! iauxl            ! e  ! --> ! pointeur sur auxl                              !
73
 
! iauxl2           ! e  ! --> ! pointeur sur auxl2                             !
74
 
! itaup            ! e  ! --> ! pointeur sur taup                              !
75
 
! iitlag           ! e  ! --> ! pointeur sur tlag                              !
76
 
! ipiil            ! e  ! --> ! pointeur sur piil                              !
77
 
! ivagau           ! e  ! --> ! pointeur sur vagaus                            !
78
 
! itsuf            ! e  ! --> ! pointeur sur tsuf                              !
79
 
! itsup            ! e  ! --> ! pointeur sur tsup                              !
80
 
! ibx              ! e  ! --> ! pointeur sur bx                                !
81
 
! igradp           ! e  ! --> ! pointeur sur gradpr                            !
82
 
! igradv           ! e  ! --> ! pointeur sur gradvf                            !
83
 
! icroul           ! e  ! --> ! pointeur sur croule                            !
84
 
! itepct           ! e  ! --> ! pointeur sur tempct                            !
85
 
! itsfex           ! e  ! --> ! pointeur sur tsfext                            !
86
 
! itsvar           ! e  ! --> ! pointeur sur tsvar                             !
87
 
! icpgd1           ! e  ! --> ! pointeur sur cpgd1                             !
88
 
! icpgd2           ! e  ! --> ! pointeur sur cpgd2                             !
89
 
! icpght           ! e  ! --> ! pointeur sur cpght                             !
90
 
! iw1              ! e  ! --> ! pointeur sur w1                                !
91
 
! iw2              ! e  ! --> ! pointeur sur w2                                !
92
 
! iw3              ! e  ! --> ! pointeur sur w3                                !
93
 
!                  !    !     !                                                !
94
 
!                  ! tr !     !  tableaux ia/ra                                !
95
 
! ifinia           ! tr ! --> ! pointeur de la premiere cas libre dan          !
96
 
!                  ! tr !     !  dans ia en sortie                             !
97
 
! ifinra           ! tr ! --> ! pointeur de la premiere cas libre dan          !
98
 
!                  ! tr !     !  dans ia en sortie                             !
99
 
!__________________.____._____.________________________________________________.
100
 
 
101
 
!     TYPE : E (ENTIER), R (REEL), A (ALPHANUMERIQUE), T (TABLEAU)
102
 
!            L (LOGIQUE)   .. ET TYPES COMPOSES (EX : TR TABLEAU REEL)
103
 
!     MODE : <-- donnee, --> resultat, <-> Donnee modifiee
104
 
!            --- tableau de travail
105
 
!===============================================================================
106
 
 
107
 
implicit none
108
 
 
109
 
!===============================================================================
110
 
! Common blocks
111
 
!===============================================================================
112
 
 
113
 
include "paramx.h"
114
 
include "entsor.h"
115
 
include "lagpar.h"
116
 
include "lagran.h"
117
 
 
118
 
!===============================================================================
119
 
 
120
 
! Arguments
121
 
 
122
 
integer          idbia0 , idbra0
123
 
integer          nfabor , ncelet , nfac
124
 
integer          nbpmax , nvp    , nvp1   , nvep  , nivep
125
 
integer          iindep , iibord , iettpa , iauxl , iauxl2
126
 
integer          itaup  , iitlag , ipiil
127
 
integer          ivagau , itsuf  , itsup  , ibx
128
 
integer          igradp , igradv , icroul
129
 
integer          itepct , itsfex , itsvar
130
 
integer          icpgd1 , icpgd2 , icpght
131
 
integer          ibrgau , itebru
132
 
integer          iw1     , iw2    , iw3
133
 
integer          ifinia , ifinra
134
 
 
135
 
! Local variables
136
 
 
137
 
integer          idebia , idebra
138
 
 
139
 
!===============================================================================
140
 
 
141
 
!---> INITIALISATION
142
 
 
143
 
idebia = idbia0
144
 
idebra = idbra0
145
 
 
146
 
!---> PLACE MEMOIRE RESERVEE AVEC DEFINITION DE IFINIA IFINRA
147
 
 
148
 
 
149
 
iibord =       idebia
150
 
ifinia =       iibord + nbpmax
151
 
 
152
 
iindep = ifinia
153
 
ifinia = iindep + nbpmax
154
 
 
155
 
iettpa =       idebra
156
 
iauxl  =       iettpa + nbpmax * nvp
157
 
itaup  =       iauxl  + nbpmax * 3
158
 
iitlag =       itaup  + nbpmax
159
 
ipiil  =       iitlag + nbpmax * 3
160
 
ivagau =       ipiil  + nbpmax * 3
161
 
itsuf  =       ivagau + nbpmax * nvgaus
162
 
itsup  =       itsuf  + nbpmax * 3
163
 
ibx    =       itsup  + nbpmax * 3
164
 
itsvar =       ibx    + nbpmax * 3 * 2
165
 
igradp =       itsvar + nbpmax * nvp1
166
 
iw1    =       igradp + ncelet * 3
167
 
iw2    =       iw1    + ncelet
168
 
iw3    =       iw2    + ncelet
169
 
ifinra =       iw3    + ncelet
170
 
 
171
 
if ( (iphyla.eq.1 .and. itpvar.eq.1) .or.                         &
172
 
      iphyla.eq.2                         ) then
173
 
  itepct = ifinra
174
 
  ifinra = itepct + 2*nbpmax
175
 
else
176
 
  itepct = 1
177
 
endif
178
 
 
179
 
if (iilagr.eq.2) then
180
 
  itsfex = ifinra
181
 
  ifinra = itsfex + nbpmax
182
 
else
183
 
  itsfex = 1
184
 
endif
185
 
 
186
 
if ( iilagr.eq.2 .and. iphyla.eq.2                                &
187
 
                 .and. ltsthe .eq.1 ) then
188
 
  icpgd1 = ifinra
189
 
  icpgd2 = icpgd1 + nbpmax
190
 
  icpght = icpgd2 + nbpmax
191
 
  ifinra = icpght + nbpmax
192
 
else
193
 
  icpgd1 = 1
194
 
  icpgd2 = 1
195
 
  icpght = 1
196
 
endif
197
 
 
198
 
if (modcpl.gt.0) then
199
 
  igradv =     ifinra
200
 
  ifinra =     igradv + ncelet * 9
201
 
else
202
 
  igradv =  1
203
 
endif
204
 
 
205
 
if (iroule.eq.1) then
206
 
  icroul = ifinra
207
 
  ifinra = icroul + ncelet
208
 
else
209
 
  icroul = 1
210
 
endif
211
 
 
212
 
if ( lamvbr .eq. 1 ) then
213
 
  ibrgau = ifinra
214
 
  itebru = ibrgau + nbpmax * nbrgau
215
 
  ifinra = itebru + nbpmax
216
 
else
217
 
  ibrgau = 1
218
 
  itebru = 1
219
 
endif
220
 
 
221
 
if (nordre.eq.2) then
222
 
  iauxl2 = ifinra
223
 
  ifinra = iauxl2 + nbpmax*7
224
 
else
225
 
  iauxl2 = 1
226
 
endif
227
 
 
228
 
!---> VERIFICATION
229
 
 
230
 
CALL IASIZE('MEMLA2',IFINIA)
231
 
!     ==========
232
 
 
233
 
CALL RASIZE('MEMLA2',IFINRA)
234
 
!     ==========
235
 
 
236
 
return
237
 
end subroutine