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

« back to all changes in this revision

Viewing changes to users/base/usaste.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:
2
2
 
3
3
!VERS
4
4
 
5
 
 
6
 
!     This file is part of the Code_Saturne Kernel, element of the
7
 
!     Code_Saturne CFD tool.
8
 
 
9
 
!     Copyright (C) 1998-2008 EDF S.A., France
10
 
 
11
 
!     contact: saturne-support@edf.fr
12
 
 
13
 
!     The Code_Saturne Kernel is free software; you can redistribute it
14
 
!     and/or modify it under the terms of the GNU General Public License
15
 
!     as published by the Free Software Foundation; either version 2 of
16
 
!     the License, or (at your option) any later version.
17
 
 
18
 
!     The Code_Saturne Kernel is distributed in the hope that it will be
19
 
!     useful, but WITHOUT ANY WARRANTY; without even the implied warranty
20
 
!     of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
21
 
!     GNU General Public License for more details.
22
 
 
23
 
!     You should have received a copy of the GNU General Public License
24
 
!     along with the Code_Saturne Kernel; if not, write to the
25
 
!     Free Software Foundation, Inc.,
26
 
!     51 Franklin St, Fifth Floor,
27
 
!     Boston, MA  02110-1301  USA
28
 
 
29
 
!-------------------------------------------------------------------------------
30
 
!-------------------------------------------------------------------------------
 
5
! This file is part of Code_Saturne, a general-purpose CFD tool.
 
6
!
 
7
! Copyright (C) 1998-2011 EDF S.A.
 
8
!
 
9
! This program is free software; you can redistribute it and/or modify it under
 
10
! the terms of the GNU General Public License as published by the Free Software
 
11
! Foundation; either version 2 of the License, or (at your option) any later
 
12
! version.
 
13
!
 
14
! This program is distributed in the hope that it will be useful, but WITHOUT
 
15
! ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS
 
16
! FOR A PARTICULAR PURPOSE.  See the GNU General Public License for more
 
17
! details.
 
18
!
 
19
! You should have received a copy of the GNU General Public License along with
 
20
! this program; if not, write to the Free Software Foundation, Inc., 51 Franklin
 
21
! Street, Fifth Floor, Boston, MA 02110-1301, USA.
 
22
 
 
23
!-------------------------------------------------------------------------------
 
24
 
31
25
subroutine usaste &
32
26
!================
33
27
 
34
 
 ( idbia0 , idbra0 ,                                              &
35
 
   ndim   , ncelet , ncel   , nfac   , nfabor , nfml   , nprfml , &
36
 
   nnod   , lndfac , lndfbr , ncelbr ,                            &
37
 
   nideve , nrdeve , nituse , nrtuse ,                            &
38
 
   ifacel , ifabor , ifmfbr , ifmcel , iprfml , maxelt , lstelt , &
39
 
   ipnfac , nodfac , ipnfbr , nodfbr , idfstr ,                   &
40
 
   idevel , ituser , ia     ,                                     &
41
 
   xyzcen , surfac , surfbo , cdgfac , cdgfbo , xyznod , volume , &
42
 
   rdevel , rtuser , ra     )
43
 
 
44
 
 
 
28
 ( idfstr )
45
29
 
46
30
!===============================================================================
47
31
! Purpose:
65
49
!__________________.____._____.________________________________________________.
66
50
! name             !type!mode ! role                                           !
67
51
!__________________!____!_____!________________________________________________!
68
 
! idbia0           ! i  ! <-- ! number of first free position in ia            !
69
 
! idbra0           ! i  ! <-- ! number of first free position in ra            !
70
 
! ndim             ! i  ! <-- ! spatial dimension                              !
71
 
! ncelet           ! i  ! <-- ! number of extended (real + ghost) cells        !
72
 
! ncel             ! i  ! <-- ! number of cells                                !
73
 
! nfac             ! i  ! <-- ! number of interior faces                       !
74
 
! nfabor           ! i  ! <-- ! number of boundary faces                       !
75
 
! nfml             ! i  ! <-- ! number of families (group classes)             !
76
 
! nprfml           ! i  ! <-- ! number of properties per family (group class)  !
77
 
! nnod             ! i  ! <-- ! number of vertices                             !
78
 
! lndfac           ! i  ! <-- ! size of nodfac indexed array                   !
79
 
! lndfbr           ! i  ! <-- ! size of nodfbr indexed array                   !
80
 
! ncelbr           ! i  ! <-- ! number of cells with faces on boundary         !
81
 
! nideve, nrdeve   ! i  ! <-- ! sizes of idevel and rdevel arrays              !
82
 
! nituse, nrtuse   ! i  ! <-- ! sizes of ituser and rtuser arrays              !
83
 
! ifacel(2, nfac)  ! ia ! <-- ! interior faces -> cells connectivity           !
84
 
! ifabor(nfabor)   ! ia ! <-- ! boundary faces -> cells connectivity           !
85
 
! ifmfbr(nfabor)   ! ia ! <-- ! boundary face family numbers                   !
86
 
! ifmcel(ncelet)   ! ia ! <-- ! cell family numbers                            !
87
 
! iprfml           ! ia ! <-- ! property numbers per family                    !
88
 
!  (nfml, nprfml)  !    !     !                                                !
89
 
! maxelt           ! i  ! <-- ! max number of cells and faces (int/boundary)   !
90
 
! lstelt(maxelt)   ! ia ! --- ! work array                                     !
91
 
! ipnfac(nfac+1)   ! ia ! <-- ! interior faces -> vertices index (optional)    !
92
 
! nodfac(lndfac)   ! ia ! <-- ! interior faces -> vertices list (optional)     !
93
 
! ipnfbr(nfabor+1) ! ia ! <-- ! boundary faces -> vertices index (optional)    !
94
 
! nodfbr(lndfbr)   ! ia ! <-- ! boundary faces -> vertices list (optional)     !
95
52
! idfstr(nfabor)   ! ia ! <-- ! boundary faces -> structure definition         !
96
 
! idevel(nideve)   ! ia ! <-- ! integer work array for temporary development   !
97
 
! ituser(nituse)   ! ia ! <-- ! user-reserved integer work array               !
98
53
! ia(*)            ! ia ! --- ! main integer work array                        !
99
 
! xyzcen           ! ra ! <-- ! cell centers                                   !
100
 
!  (ndim, ncelet)  !    !     !                                                !
101
 
! surfac           ! ra ! <-- ! interior faces surface vectors                 !
102
 
!  (ndim, nfac)    !    !     !                                                !
103
 
! surfbo           ! ra ! <-- ! boundary faces surface vectors                 !
104
 
!  (ndim, nfabor)  !    !     !                                                !
105
 
! cdgfac           ! ra ! <-- ! interior faces centers of gravity              !
106
 
!  (ndim, nfac)    !    !     !                                                !
107
 
! cdgfbo           ! ra ! <-- ! boundary faces centers of gravity              !
108
 
!  (ndim, nfabor)  !    !     !                                                !
109
 
! xyznod           ! ra ! <-- ! vertex coordinates (optional)                  !
110
 
!  (ndim, nnod)    !    !     !                                                !
111
 
! volume(ncelet)   ! ra ! <-- ! cell volumes                                   !
112
 
! rdevel(nrdeve)   ! ra ! <-> ! real work array for temporary development      !
113
 
! rtuser(nrtuse)   ! ra ! <-- ! user-reserved real work array                  !
114
54
! ra(*)            ! ra ! --- ! main real work array                           !
115
55
!__________________!____!_____!________________________________________________!
116
56
 
119
59
!     mode: <-- input, --> output, <-> modifies data, --- work array
120
60
!===============================================================================
121
61
 
 
62
!===============================================================================
 
63
! Module files
 
64
!===============================================================================
 
65
 
 
66
use paramx
 
67
use cstnum
 
68
use optcal
 
69
use entsor
 
70
use albase
 
71
use parall
 
72
use period
 
73
use alaste
 
74
use mesh
 
75
 
 
76
!===============================================================================
 
77
 
122
78
implicit none
123
79
 
124
 
!===============================================================================
125
 
! Common blocks
126
 
!===============================================================================
127
 
 
128
 
include "paramx.h"
129
 
include "cstnum.h"
130
 
include "optcal.h"
131
 
include "entsor.h"
132
 
include "pointe.h"
133
 
include "albase.h"
134
 
include "period.h"
135
 
include "parall.h"
136
 
include "alaste.h"
137
 
 
138
 
!===============================================================================
139
 
 
140
80
! Arguments
141
81
 
142
 
integer          idbia0 , idbra0
143
 
integer          ndim   , ncelet , ncel   , nfac   , nfabor
144
 
integer          nfml   , nprfml
145
 
integer          nnod   , lndfac , lndfbr , ncelbr
146
82
integer          nbstru
147
 
integer          nideve , nrdeve , nituse , nrtuse
148
83
 
149
 
integer          ifacel(2,nfac) , ifabor(nfabor)
150
 
integer          ifmfbr(nfabor) , ifmcel(ncelet)
151
 
integer          iprfml(nfml,nprfml)
152
 
integer          maxelt, lstelt(maxelt)
153
 
integer          ipnfac(nfac+1), nodfac(lndfac)
154
 
integer          ipnfbr(nfabor+1), nodfbr(lndfbr)
155
84
integer          idfstr(nfabor)
156
 
integer          idevel(nideve), ituser(nituse)
157
 
integer          ia(*)
158
 
 
159
 
double precision xyzcen(ndim,ncelet)
160
 
double precision surfac(ndim,nfac), surfbo(ndim,nfabor)
161
 
double precision cdgfac(ndim,nfac), cdgfbo(ndim,nfabor)
162
 
double precision xyznod(ndim,nnod), volume(ncelet)
163
 
double precision rdevel(nrdeve), rtuser(nrtuse), ra(*)
164
85
 
165
86
! Local variables
166
87
 
167
 
integer          idebia, idebra
168
88
integer          ifac
169
89
integer          ilelt, nlelt
170
90
 
 
91
integer, allocatable, dimension(:) :: lstelt
 
92
 
171
93
!===============================================================================
172
94
! TEST_TO_REMOVE_FOR_USE_OF_SUBROUTINE_START
173
95
 
181
103
 
182
104
!===============================================================================
183
105
! 1.  INITIALIZATION
184
 
 
185
106
!===============================================================================
186
107
 
187
 
idebia = idbia0
188
 
idebra = idbra0
 
108
! Allocate a temporary array for boundary faces selection
 
109
allocate(lstelt(nfabor))
 
110
 
189
111
 
190
112
!===============================================================================
191
113
! 2.  Definition of external structures
250
172
 
251
173
asddlf(3,2) = 0
252
174
 
253
 
! --- Activation of Code_Saturne/Code_Aster synchronized chronological output.
254
 
!     (ISYNCP = 1 : Synchronized output, ISYNCP = 0: Non synchronized output)
255
 
 
256
 
isyncp = 1
257
 
 
258
175
!----
259
176
! Formats
260
177
!----
262
179
!----
263
180
! End
264
181
!----
 
182
 
 
183
! Deallocate the temporary array
 
184
deallocate(lstelt)
 
185
 
265
186
return
266
 
 
267
187
end subroutine