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

« back to all changes in this revision

Viewing changes to src/base/cscini.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
1
!-------------------------------------------------------------------------------
2
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
 
3
! This file is part of Code_Saturne, a general-purpose CFD tool.
 
4
!
 
5
! Copyright (C) 1998-2011 EDF S.A.
 
6
!
 
7
! This program is free software; you can redistribute it and/or modify it under
 
8
! the terms of the GNU General Public License as published by the Free Software
 
9
! Foundation; either version 2 of the License, or (at your option) any later
 
10
! version.
 
11
!
 
12
! This program is distributed in the hope that it will be useful, but WITHOUT
 
13
! ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS
 
14
! FOR A PARTICULAR PURPOSE.  See the GNU General Public License for more
 
15
! details.
 
16
!
 
17
! You should have received a copy of the GNU General Public License along with
 
18
! this program; if not, write to the Free Software Foundation, Inc., 51 Franklin
 
19
! Street, Fifth Floor, Boston, MA 02110-1301, USA.
25
20
 
26
21
!-------------------------------------------------------------------------------
27
22
 
28
23
subroutine cscini &
29
24
!================
30
25
 
31
 
 ( idbia0 , idbra0 ,                                              &
32
 
   ndim   , ncelet , ncel   , nfac   , nfabor , nfml   , nprfml , &
33
 
   nnod   , lndfac , lndfbr , ncelbr ,                            &
34
 
   nvar   , nscal  , nphas  ,                                     &
35
 
   nideve , nrdeve , nituse , nrtuse ,                            &
36
 
   ifacel , ifabor , ifmfbr , ifmcel , iprfml ,                   &
37
 
   ipnfac , nodfac , ipnfbr , nodfbr ,                            &
38
 
   idevel , ituser , ia     ,                                     &
39
 
   xyzcen , surfac , surfbo , cdgfac , cdgfbo , xyznod ,          &
40
 
   rdevel , rtuser , ra     )
 
26
 ( nvar   , nscal  )
41
27
 
42
28
!===============================================================================
43
29
! FONCTION :
59
45
!            --- tableau de travail
60
46
!===============================================================================
61
47
 
 
48
!===============================================================================
 
49
! Module files
 
50
!===============================================================================
 
51
 
 
52
use paramx
 
53
use numvar
 
54
use optcal
 
55
use cstphy
 
56
use cstnum
 
57
use entsor
 
58
use parall
 
59
use period
 
60
use albase
 
61
use cplsat
 
62
 
 
63
!===============================================================================
 
64
 
62
65
implicit none
63
66
 
64
 
!===============================================================================
65
 
! Common blocks
66
 
!===============================================================================
67
 
 
68
 
include "paramx.h"
69
 
include "pointe.h"
70
 
include "numvar.h"
71
 
include "optcal.h"
72
 
include "cstphy.h"
73
 
include "cstnum.h"
74
 
include "entsor.h"
75
 
include "parall.h"
76
 
include "period.h"
77
 
include "albase.h"
78
 
include "cplsat.h"
79
 
 
80
 
!===============================================================================
81
 
 
82
67
! Arguments
83
68
 
84
 
integer          idbia0 , idbra0
85
 
integer          ndim   , ncelet , ncel   , nfac   , nfabor
86
 
integer          nfml   , nprfml
87
 
integer          nnod   , lndfac , lndfbr , ncelbr
88
 
integer          nvar   , nscal  , nphas
89
 
integer          nideve , nrdeve , nituse , nrtuse
90
 
 
91
 
integer          ifacel(2,nfac) , ifabor(nfabor)
92
 
integer          ifmfbr(nfabor) , ifmcel(ncelet)
93
 
integer          iprfml(nfml,nprfml)
94
 
integer          ipnfac(nfac+1), nodfac(lndfac)
95
 
integer          ipnfbr(nfabor+1), nodfbr(lndfbr)
96
 
integer          idevel(nideve), ituser(nituse), ia(*)
97
 
 
98
 
double precision xyzcen(ndim,ncelet)
99
 
double precision surfac(ndim,nfac), surfbo(ndim,nfabor)
100
 
double precision cdgfac(ndim,nfac), cdgfbo(ndim,nfabor)
101
 
double precision xyznod(ndim,nnod)
102
 
double precision rdevel(nrdeve), rtuser(nrtuse), ra(*)
 
69
integer          nvar   , nscal
 
70
 
 
71
 
103
72
 
104
73
! Local variables
105
74
 
106
 
integer          idebia , idebra , ifinia , ifinra
107
 
integer          iphas
108
75
integer          numcpl
109
76
integer          imobmx , ialemx , nvcpmx, ifcpmx
110
77
 
111
78
!===============================================================================
112
79
 
113
 
idebia = idbia0
114
 
idebra = idbra0
115
80
 
116
81
do numcpl = 1, nbrcpl
117
82
 
171
136
  ! modeles RANS et laminaires, sauf pour le modele v2f (dans ce cas
172
137
  ! il n'y a que du couplage mono-modele)
173
138
 
174
 
  do iphas = 1, nphas
175
 
 
176
 
    call tbicpl(numcpl, 1, 1, iturb(iphas), iturcp(numcpl,iphas))
177
 
    !==========
178
 
 
179
 
    if (iturb(iphas).eq.50.and.iturcp(numcpl,iphas).ne.50) then
180
 
      write(nfecra,1000) numcpl
181
 
      call csexit(1)
182
 
      !==========
183
 
    elseif (itytur(iphas).eq.4.and.                               &
184
 
            iturcp(numcpl,iphas)/10.ne.4) then
185
 
      write(nfecra,1001) numcpl
186
 
      call csexit(1)
187
 
      !==========
188
 
    endif
189
 
 
190
 
  enddo
 
139
  call tbicpl(numcpl, 1, 1, iturb, iturcp(numcpl))
 
140
  !==========
 
141
 
 
142
  if (iturb.eq.50.and.iturcp(numcpl).ne.50) then
 
143
    write(nfecra,1000) numcpl
 
144
    call csexit(1)
 
145
    !==========
 
146
  elseif (iturb.eq.51.and.iturcp(numcpl).ne.51) then
 
147
    write(nfecra,1002) numcpl
 
148
    call csexit(1)
 
149
    !==========
 
150
  elseif (itytur.eq.4.and.                               &
 
151
       iturcp(numcpl)/10.ne.4) then
 
152
    write(nfecra,1001) numcpl
 
153
    call csexit(1)
 
154
    !==========
 
155
  endif
191
156
 
192
157
enddo
193
158
 
203
168
'@    =========                                               ',/,&
204
169
'@    LES MODELES DE TURBULENCE POUR LE COUPLAGE ' ,I10        ,/,&
205
170
'@    SONT DIFFERENTS ALORS QUE L UN DES MODELES EST LE       ',/,&
206
 
'@    V2F. CE CAS DE FIGURE N''EST PAS PRIS                   ',/,&
 
171
'@    V2F PHI_FBAR. CE CAS DE FIGURE N''EST PAS PRIS          ',/,&
 
172
'@    EN COMPTE POUR LE MOMENT.                               ',/,&
 
173
'@                                                            ',/,&
 
174
'@  Le calcul ne peut etre execute.                           ',/,&
 
175
'@                                                            ',/,&
 
176
'@  Verifier usini1.                                          ',/,&
 
177
'@                                                            ',/,&
 
178
'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@',/,&
 
179
'@                                                            ',/)
 
180
 1002 format(                                                           &
 
181
'@                                                            ',/,&
 
182
'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@',/,&
 
183
'@                                                            ',/,&
 
184
'@ @@ ATTENTION : ARRET A L''ENTREE DES DONNEES               ',/,&
 
185
'@    =========                                               ',/,&
 
186
'@    LES MODELES DE TURBULENCE POUR LE COUPLAGE ' ,I10        ,/,&
 
187
'@    SONT DIFFERENTS ALORS QUE L UN DES MODELES EST LE       ',/,&
 
188
'@    V2F BL-V2/K. CE CAS DE FIGURE N''EST PAS PRIS           ',/,&
207
189
'@    EN COMPTE POUR LE MOMENT.                               ',/,&
208
190
'@                                                            ',/,&
209
191
'@  Le calcul ne peut etre execute.                           ',/,&