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

« back to all changes in this revision

Viewing changes to src/base/vorini.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 vorini &
29
 
!================
30
 
 
31
 
 ( ncevor , nvor   , ient   ,                                     &
32
 
   ivorce , xyz    , yzcel  , xu     , xv     , xw     ,          &
33
 
   yzvor  , signv  , temps  , tpslim )
34
 
 
35
 
!===============================================================================
36
 
!  FONCTION  :
37
 
!  ----------
38
 
 
39
 
! INITIALISATION DE LA METHODE DES VORTEX POUR LES ENTREES EN L.E.S.
40
 
 
41
 
!-------------------------------------------------------------------------------
42
 
! Arguments
43
 
!__________________.____._____.________________________________________________.
44
 
! name             !type!mode ! role                                           !
45
 
!__________________!____!_____!________________________________________________!
46
 
! ncevor           ! e  ! <-- ! nombre de face a l'entree ou est               !
47
 
!                  !    !     ! utilise la methode                             !
48
 
! nvor             ! e  ! <-- ! nombre de vortex a l'entree                    !
49
 
! ient             ! e  ! <-- ! numero de l'entree                             !
50
 
! ivorce           ! te ! <-- ! numero du vortex le plus proche d'une          !
51
 
!     (nvomax)     !    !     ! face donnee                                    !
52
 
! xyz(icvmax,3)    !    ! <-- ! coordonnees des faces d'entree dans            !
53
 
!                  !    !     ! le calcul                                      !
54
 
! yzcel            ! tr ! <-- ! coordonnees des faces d'entree dans            !
55
 
!   (icvmax ,2)    !    !     ! le referentiel local                           !
56
 
! xu(icvmax)       ! tr ! --- ! composante de vitesse principale               !
57
 
! xv(icvmax)       ! tr ! <-- ! composantes de vitesse transverses             !
58
 
! xw(icvmax)       ! tr ! <-- !                                                !
59
 
! yzvor            ! tr ! <-- ! coordonnees du centre des vortex               !
60
 
!   (nvomax,2)     !    !     !                                                !
61
 
! signv(nvomax)    ! tr ! <-- ! sens de rotation des vortex                    !
62
 
! temps            ! tr ! <-- ! temps ecoule depuis la creation                !
63
 
!     (nvomax)     !    !     ! du vortex                                      !
64
 
! tpslim           ! tr ! <-- ! duree de vie du vortex                         !
65
 
!     (nvomax)     !    !     !                                                !
66
 
!__________________.____._____.________________________________________________.
67
 
 
68
 
!     TYPE : E (ENTIER), R (REEL), A (ALPHANUMERIQUE), T (TABLEAU)
69
 
!            L (LOGIQUE)   .. ET TYPES COMPOSES (EX : TR TABLEAU REEL)
70
 
!     MODE : <-- donnee, --> resultat, <-> Donnee modifiee
71
 
!            --- tableau de travail
72
 
!===============================================================================
73
 
 
74
 
implicit none
75
 
 
76
 
!===============================================================================
77
 
! Common blocks
78
 
!===============================================================================
79
 
 
80
 
include "paramx.h"
81
 
include "cstphy.h"
82
 
include "cstnum.h"
83
 
include "optcal.h"
84
 
include "entsor.h"
85
 
include "vortex.h"
86
 
 
87
 
!===============================================================================
88
 
 
89
 
! Arguments
90
 
 
91
 
integer          ncevor , nvor   , ient
92
 
integer          ivorce(nvomax)
93
 
 
94
 
double precision xyz(icvmax,3)   , yzcel(icvmax,2)
95
 
double precision xu(icvmax)      , xv(icvmax)      , xw(icvmax)
96
 
double precision yzvor(nvomax,2) , signv(nvomax)
97
 
double precision temps(nvomax)   , tpslim(nvomax)
98
 
 
99
 
 
100
 
! Local variables
101
 
 
102
 
integer          ii, jj, kk, iii, iun, ivort, iient, iok
103
 
 
104
 
double precision dd
105
 
double precision drand(1), phidat, xx, yy, zz
106
 
double precision uu, vv, ww
107
 
double precision u_vor, ek_vor, ee_vor
108
 
 
109
 
integer          ilect
110
 
data             ilect /0/
111
 
save             ilect
112
 
!===============================================================================
113
 
! 1. CALCUL DU REPERE LOCAL ET CHANGEMENT DE REPERE
114
 
!===============================================================================
115
 
 
116
 
ilect = ilect + 1
117
 
if(ilect.eq.1) then
118
 
  write(nfecra,1000) nnent, isuivo
119
 
endif
120
 
 
121
 
if(icas(ient).eq.1.or.icas(ient).eq.2.or.icas(ient).eq.3) then
122
 
 
123
 
  dir3(1,ient)=dir1(2,ient)*dir2(3,ient)-dir1(3,ient)*dir2(2,ient)
124
 
  dir3(2,ient)=dir1(3,ient)*dir2(1,ient)-dir1(1,ient)*dir2(3,ient)
125
 
  dir3(3,ient)=dir1(1,ient)*dir2(2,ient)-dir1(2,ient)*dir2(1,ient)
126
 
 
127
 
elseif(icas(ient).eq.4) then
128
 
 
129
 
!     On s'aide du vecteur surface d'une face de l'entree (supposee plane)
130
 
!     pour definir le repere local
131
 
 
132
 
  vv = sqrt(surf(1,ient)**2 + surf(2,ient)**2 + surf(3,ient)**2)
133
 
 
134
 
  dir3(1,ient) = -surf(1,ient)/vv
135
 
  dir3(2,ient) = -surf(2,ient)/vv
136
 
  dir3(3,ient) = -surf(3,ient)/vv
137
 
 
138
 
!     On se fixe, par exemple, x1 = 0 et y1 = 1 et on norme le vecteur
139
 
 
140
 
  dir1(1,ient) = 0.d0
141
 
  dir1(2,ient) = 1.d0
142
 
  if (abs(dir3(3,ient)).gt.epzero) then
143
 
    dir1(3,ient) = -dir3(2,ient)/dir3(3,ient)
144
 
  else
145
 
    dir1(3,ient) = 0.d0
146
 
  endif
147
 
 
148
 
  vv = sqrt(dir1(1,ient)**2 + dir1(2,ient)**2 + dir1(3,ient)**2)
149
 
 
150
 
  dir1(1,ient) = dir1(1,ient)/vv
151
 
  dir1(2,ient) = dir1(2,ient)/vv
152
 
  dir1(3,ient) = dir1(3,ient)/vv
153
 
 
154
 
!     On obtient le dernier vecteur par produit vectoriel des deux autres
155
 
 
156
 
  dir2(1,ient) =                                                  &
157
 
    dir3(2,ient)*dir1(3,ient) - dir3(3,ient)*dir1(2,ient)
158
 
  dir2(2,ient) =                                                  &
159
 
    dir3(3,ient)*dir1(1,ient) - dir3(1,ient)*dir1(3,ient)
160
 
  dir2(3,ient) =                                                  &
161
 
    dir3(1,ient)*dir1(2,ient) - dir3(2,ient)*dir1(1,ient)
162
 
 
163
 
endif
164
 
 
165
 
! - Changement de repere (on suppose que les vecteurs sont normes)
166
 
 
167
 
do ii = 1, ncevor
168
 
  xx = xyz(ii,1) - cen(1,ient)
169
 
  yy = xyz(ii,2) - cen(2,ient)
170
 
  zz = xyz(ii,3) - cen(3,ient)
171
 
  yzcel(ii,1) = dir1(1,ient)*xx+dir1(2,ient)*yy+dir1(3,ient)*zz
172
 
  yzcel(ii,2) = dir2(1,ient)*xx+dir2(2,ient)*yy+dir2(3,ient)*zz
173
 
enddo
174
 
 
175
 
! - Dimensions min et max de l entree
176
 
 
177
 
ymax(ient) = -grand
178
 
ymin(ient) =  grand
179
 
zmax(ient) = -grand
180
 
zmin(ient) =  grand
181
 
do ii = 1, ncevor
182
 
  ymax(ient) = max(ymax(ient),yzcel(ii,1))
183
 
  ymin(ient) = min(ymin(ient),yzcel(ii,1))
184
 
  zmax(ient) = max(zmax(ient),yzcel(ii,2))
185
 
  zmin(ient) = min(zmin(ient),yzcel(ii,2))
186
 
enddo
187
 
 
188
 
! - Verification
189
 
 
190
 
if(icas(ient).eq.1) then
191
 
  if(lly(ient).lt.ymax(ient)-ymin(ient).or.                       &
192
 
       llz(ient).lt.zmax(ient)-zmin(ient)) then
193
 
    write(nfecra,2000) ient
194
 
    call csexit(1)
195
 
  endif
196
 
elseif(icas(ient).eq.2) then
197
 
  if(lld(ient).lt.ymax(ient)-ymin(ient).or.                       &
198
 
       lld(ient).lt.zmax(ient)-zmin(ient)) then
199
 
    write(nfecra,2000) ient
200
 
    call csexit(1)
201
 
  endif
202
 
endif
203
 
!===============================================================================
204
 
! 2. IMPRESSIONS DES PARAMETES A CHAQUE ENTREE
205
 
!===============================================================================
206
 
 
207
 
call vorimp(ient)
208
 
!==========
209
 
!===============================================================================
210
 
! 3. REMPLISSAGE DES TABLEAUX DE DONNEES EN ENTREE
211
 
!===============================================================================
212
 
 
213
 
iun = 1
214
 
 
215
 
if(icas(ient).eq.1.or.icas(ient).eq.2.or.icas(ient).eq.3) then
216
 
  open(file=ficvor(ient),unit=impdvo)
217
 
  rewind(impdvo)
218
 
  do ii = 1, ndat(ient)
219
 
    read(impdvo,*)                                                &
220
 
         xdat(ii,ient) , ydat(ii,ient) , zdat(ii,ient)  ,         &
221
 
         udat(ii,ient) , vdat(ii,ient) , wdat(ii,ient)  ,         &
222
 
         dudat(ii,ient), kdat(ii,ient) , epsdat(ii,ient)
223
 
  enddo
224
 
  close(impdvo)
225
 
  write(nfecra,3000)
226
 
elseif(icas(ient).eq.4) then
227
 
  xdat(1,ient)   = cen(1,ient)
228
 
  ydat(1,ient)   = cen(2,ient)
229
 
  zdat(1,ient)   = cen(3,ient)
230
 
  udat(1,ient)   = udebit(ient)
231
 
  vdat(1,ient)   = 0.d0
232
 
  wdat(1,ient)   = 0.d0
233
 
  dudat(1,ient)  = 0.d0
234
 
  kdat(1,ient)   = kdebit(ient)
235
 
  epsdat(1,ient) = edebit(ient)
236
 
endif
237
 
 
238
 
! On suppose que les donnees sont fournies
239
 
! dans le repere du calcul (et non dans le repere local).
240
 
! C'est plus simple pour l'utilisateur, et plus
241
 
! naturel pour faire du couplage
242
 
 
243
 
do ii = 1, ndat(ient)
244
 
  xx = xdat(ii,ient) - cen(1,ient)
245
 
  yy = ydat(ii,ient) - cen(2,ient)
246
 
  zz = zdat(ii,ient) - cen(3,ient)
247
 
  uu = udat(ii,ient)
248
 
  vv = vdat(ii,ient)
249
 
  ww = wdat(ii,ient)
250
 
  ydat(ii,ient) = dir1(1,ient)*xx+dir1(2,ient)*yy+dir1(3,ient)*zz
251
 
  zdat(ii,ient) = dir2(1,ient)*xx+dir2(2,ient)*yy+dir2(3,ient)*zz
252
 
  udat(ii,ient) = dir3(1,ient)*uu+dir3(2,ient)*vv+dir3(3,ient)*ww
253
 
  vdat(ii,ient) = dir1(1,ient)*uu+dir1(2,ient)*vv+dir1(3,ient)*ww
254
 
  wdat(ii,ient) = dir2(1,ient)*uu+dir2(2,ient)*vv+dir2(3,ient)*ww
255
 
enddo
256
 
 
257
 
! --- Verfication des donnees
258
 
 
259
 
iok = 0
260
 
do ii = 1, ndat(ient)
261
 
  if(udat(ii,ient).le.0.d0.or.kdat(ii,ient).le.0.d0.or.           &
262
 
       epsdat(ii,ient).le.0.d0) then
263
 
    write(nfecra,3100) ient
264
 
    call csexit (1)
265
 
  endif
266
 
  if(icas(ient).eq.1) then
267
 
    if(ydat(ii,ient).lt.-lly(ient)/2.d0.or.                       &
268
 
         ydat(ii,ient).gt.lly(ient)/2.d0.or.                      &
269
 
         zdat(ii,ient).lt.-llz(ient)/2.d0.or.                     &
270
 
         zdat(ii,ient).gt.llz(ient)/2.d0) then
271
 
      iok = iok + 1
272
 
    endif
273
 
  elseif(icas(ient).eq.2) then
274
 
    if(ydat(ii,ient).lt.-lld(ient)/2.d0.or.                       &
275
 
         ydat(ii,ient).gt.lld(ient)/2.d0.or.                      &
276
 
         zdat(ii,ient).lt.-lld(ient)/2.d0.or.                     &
277
 
         zdat(ii,ient).gt.lld(ient)/2.d0) then
278
 
      iok = iok + 1
279
 
    endif
280
 
  endif
281
 
enddo
282
 
 
283
 
if(iok.gt.0) then
284
 
  write(nfecra,3200) ient
285
 
endif
286
 
 
287
 
!===============================================================================
288
 
! 4. LECTURE DU FICHIER SUITE / INITIALISATION DU CHAMP DE VORTEX
289
 
!===============================================================================
290
 
 
291
 
if(isuivo.eq.1) then
292
 
 
293
 
  if(ient.eq.1) then
294
 
    open(unit=impmvo,file=ficmvo)
295
 
    rewind(impmvo)
296
 
  endif
297
 
 
298
 
  read(impmvo,100) iient
299
 
  read(impmvo,100) ivort
300
 
  if(ivort.ne.nvor.or.iient.ne.ient) then
301
 
    write(nfecra,4500) ient, ivort, nvor
302
 
    initvo(ient) = 1
303
 
  else
304
 
    do ii = 1, nvor
305
 
      read(impmvo,200) yzvor(ii,1), yzvor(ii,2),                  &
306
 
             temps(ii), tpslim(ii), signv(ii)
307
 
    enddo
308
 
    initvo(ient) = 0
309
 
    write(nfecra,4000)
310
 
  endif
311
 
 
312
 
  if(ient.eq.nnent) then
313
 
    close(impmvo)
314
 
  endif
315
 
 
316
 
endif
317
 
 
318
 
if(isuivo.eq.0.or.initvo(ient).eq.1) then
319
 
 
320
 
!-------------------------------
321
 
!  Tirage des positions
322
 
!-------------------------------
323
 
  iun = 1
324
 
  if(icas(ient).eq.1)then
325
 
    do ii = 1, nvor
326
 
      call zufall(iun,drand(1))
327
 
      yzvor(ii,1) = lly(ient) * drand(1) - lly(ient)/2.d0
328
 
      call zufall(iun,drand(1))
329
 
      yzvor(ii,2) = llz(ient) * drand(1) - llz(ient)/2.d0
330
 
    enddo
331
 
  elseif(icas(ient).eq.2) then
332
 
    do ii = 1, nvor
333
 
 15         continue
334
 
      call zufall(iun,drand(1))
335
 
      yzvor(ii,1) = lld(ient) * drand(1) - lld(ient)/2.0d0
336
 
      call zufall(iun,drand(1))
337
 
      yzvor(ii,2) = lld(ient) * drand(1) - lld(ient)/2.0d0
338
 
      if ((yzvor(ii,1)**2+yzvor(ii,2)**2).gt.                     &
339
 
           (lld(ient)/2.d0)**2) then
340
 
        goto 15
341
 
      endif
342
 
    enddo
343
 
  elseif(icas(ient).eq.3.or.icas(ient).eq.4) then
344
 
    do ii = 1, nvor
345
 
      call zufall(iun,drand(1))
346
 
      yzvor(ii,1) = ymin(ient) + lly(ient) * drand(1)
347
 
      call zufall(iun,drand(1))
348
 
      yzvor(ii,2) = zmin(ient) + llz(ient) * drand(1)
349
 
    enddo
350
 
  endif
351
 
!--------------
352
 
! Duree de vie
353
 
!--------------
354
 
  if(itlivo(ient).eq.1) then
355
 
    do ii = 1, nvor
356
 
      call zufall(iun,drand(1))
357
 
      temps(ii) = drand(1)*tlimvo(ient)
358
 
 
359
 
! on fait cela pour que les vortex ne disparaissent pas tous
360
 
! en meme temps    .
361
 
 
362
 
      tpslim(ii) = tlimvo(ient)
363
 
    enddo
364
 
  elseif(itlivo(ient).eq.2) then
365
 
    do ii = 1, nvor
366
 
      yy = yzvor(ii,1)
367
 
      zz = yzvor(ii,2)
368
 
      iii = 0
369
 
      u_vor  =  phidat(nfecra,icas(ient),ndat(ient),yy,zz,        &
370
 
                ydat(1,ient),zdat(1,ient),udat(1,ient),iii)
371
 
      ek_vor =  phidat(nfecra,icas(ient),ndat(ient),yy,zz,        &
372
 
                ydat(1,ient),zdat(1,ient),kdat(1,ient),iii)
373
 
      ee_vor =  phidat(nfecra,icas(ient),ndat(ient),yy,zz,        &
374
 
                ydat(1,ient),zdat(1,ient),epsdat(1,ient),iii)
375
 
      tpslim(ii) = 5.d0*cmu*ek_vor**(3.d0/2.d0)/ee_vor
376
 
      tpslim(ii) = tpslim(ii)/u_vor
377
 
      temps(ii) = 0.d0
378
 
    enddo
379
 
  endif
380
 
!------------------
381
 
! Sens de rotation
382
 
!------------------
383
 
  do ii = 1, nvor
384
 
    signv(ii) = 1.d0
385
 
    call zufall(iun,drand(1))
386
 
    if (drand(1).lt.0.5d0) signv(ii) = -1.d0
387
 
  enddo
388
 
endif
389
 
 
390
 
!===============================================================================
391
 
! 5. AJOUT DE LA VITESSE MOYENNE POUR U
392
 
!===============================================================================
393
 
 
394
 
do ii = 1, ncevor
395
 
  yy = yzcel(ii,1)
396
 
  zz = yzcel(ii,2)
397
 
  iii = 0
398
 
  u_vor = phidat(nfecra,icas(ient),ndat(ient),yy,zz,              &
399
 
          ydat(1,ient),zdat(1,ient),udat(1,ient),iii)
400
 
  xu(ii)= u_vor
401
 
enddo
402
 
 
403
 
!===============================================================================
404
 
! 6. RECHERCHE DE LA FACE LA PLUS PROCHE DE CHAQUE VORTEX
405
 
!===============================================================================
406
 
do ii = 1, nvor
407
 
  kk = 0
408
 
  dd = grand
409
 
  do jj = 1, ncevor
410
 
    if(((yzcel(jj,1)-yzvor(ii,1))**2+                             &
411
 
        (yzcel(jj,2)-yzvor(ii,2))**2).lt.dd)then
412
 
      dd = (yzcel(jj,1)-yzvor(ii,1))**2                           &
413
 
          +(yzcel(jj,2)-yzvor(ii,2))**2
414
 
      kk = jj
415
 
    endif
416
 
  enddo
417
 
  ivorce(ii) = kk
418
 
enddo
419
 
 
420
 
! FORMATS
421
 
 
422
 
#if defined(_CS_LANG_FR)
423
 
 
424
 
 1000 format(                                                           &
425
 
'                                                             ',/,&
426
 
' ** METHODE DES VORTEX                                       ',/,&
427
 
'    ------------------                                       ',/,&
428
 
'       NNENT  = ',4X,I10,    ' (Nombre d entrees            )',/,&
429
 
'       ISUIVO = ',4X,I10,    ' (1 : suite de calcul         )'  )
430
 
 
431
 
 2000 format(                                                           &
432
 
'@                                                            ',/,&
433
 
'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@',/,&
434
 
'@                                                            ',/,&
435
 
'@ @@ ATTENTION : ARRET A L''ENTREE DES DONNEES               ',/,&
436
 
'@    =========                                               ',/,&
437
 
'@    LES DIMENSIONS MAX DE L''ENTREE SONT INCOMPATIBLES AVEC ',/,&
438
 
'@    LES DONNEES A L''ENTREE ',I10                            ,/,&
439
 
'@                                                            ',/,&
440
 
'@  Le calcul ne peut etre execute.                           ',/,&
441
 
'@                                                            ',/,&
442
 
'@  Verifier usvort.                                          ',/,&
443
 
'@                                                            ',/,&
444
 
'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@',/,&
445
 
'@                                                            ',/)
446
 
 
447
 
 3000 format(                                                           &
448
 
'                                                             ',/,&
449
 
' --  Fin de la lecture du fichier de donnees                 ',/)
450
 
 3100 format(                                                           &
451
 
'@                                                            ',/,&
452
 
'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@',/,&
453
 
'@                                                            ',/,&
454
 
'@ @@ ATTENTION : ARRET A L''ENTREE DES DONNEES               ',/,&
455
 
'@    =========                                               ',/,&
456
 
'@    U, K ET EPSILON SONT DES GRANDEURS QUI SONT DEFINIES    ',/,&
457
 
'@    POSITIVES DANS LE REPERE LOCAL DE L''ENTREE             ',/,&
458
 
'@                                                            ',/,&
459
 
'@    VERIFIER LE FICHIER DE DONNEE DE L''ENTREE ',I10         ,/,&
460
 
'@                                                            ',/,&
461
 
'@  Le calcul ne peut etre execute.                           ',/,&
462
 
'@                                                            ',/,&
463
 
'@  Verifier usvort.                                          ',/,&
464
 
'@                                                            ',/,&
465
 
'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@',/,&
466
 
'@                                                            ',/)
467
 
 3200 format(                                                           &
468
 
'@                                                            ',/,&
469
 
'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@',/,&
470
 
'@                                                            ',/,&
471
 
'@ @@ ATTENTION :       A L''ENTREE DES DONNEES               ',/,&
472
 
'@    =========                                               ',/,&
473
 
'@    LES DIMENSIONS MAX DE L''ENTREE SONT INCOMPATIBLES AVEC ',/,&
474
 
'@    CELLES DU FICHIER DE DONNEES                            ',/,&
475
 
'@                                                            ',/,&
476
 
'@    VERIFIER LE FICHIER DE DONNEE DE L''ENTREE ',I10         ,/,&
477
 
'@                                                            ',/,&
478
 
'@  Le calcul sera execute.                                   ',/,&
479
 
'@                                                            ',/,&
480
 
'@  Verifier usvort.                                          ',/,&
481
 
'@                                                            ',/,&
482
 
'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@',/,&
483
 
'@                                                            ',/)
484
 
 
485
 
 4000 format(                                                           &
486
 
' --  Fin de la lecture du fichier suite                      ',/)
487
 
 
488
 
 4500   format(                                                         &
489
 
'@                                                            ',/,&
490
 
'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@',/,&
491
 
'@                                                            ',/,&
492
 
'@ @@ ATTENTION :      A L''ENTREE DES DONNEES                ',/,&
493
 
'@    =========                                               ',/,&
494
 
'@  LE NOMBRE DE VORTEX A CHANGE A L''ENTREE',I10              ,/,&
495
 
'@    NVORT VALAIT PRECECEDEMENT ',I10                         ,/,&
496
 
'@    A L''ENTREE ',I10                                        ,/,&
497
 
'@    ET VAUT MAINTENANT  ',I10                                ,/,&
498
 
'@                                                            ',/,&
499
 
'@  LA METHODE EST REINITIALISE A CETTE ENTREE                ',/,&
500
 
'@                                                            ',/,&
501
 
'@  Le calcul sera execute                                    ',/,&
502
 
'@                                                            ',/,&
503
 
'@  Verifier usvort.                                          ',/,&
504
 
'@                                                            ',/,&
505
 
'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@',/,&
506
 
'@                                                            ',/)
507
 
 
508
 
 100  format(i10)
509
 
 200  format(5e13.5)
510
 
 
511
 
#else
512
 
 
513
 
 1000 format(                                                           &
514
 
'                                                             ',/,&
515
 
' ** VORTEX METHOD                                            ',/,&
516
 
'    -------------                                            ',/,&
517
 
'       NNENT  = ',4X,I10,    ' (Number of inlets            )',/,&
518
 
'       ISUIVO = ',4X,I10,    ' (1: calculation restart      )'  )
519
 
 
520
 
 2000 format(                                                           &
521
 
'@                                                            ',/,&
522
 
'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@',/,&
523
 
'@                                                            ',/,&
524
 
'@ @@ WARNING: ABORT IN THE DATA SPECIFICATION                ',/,&
525
 
'@    ========                                                ',/,&
526
 
'@    THE MAX DIMENSIONS OF THE INLET ARE INCOMPATIBLE WITH   ',/,&
527
 
'@    THE DATA AT THE INLET ',I10                              ,/,&
528
 
'@                                                            ',/,&
529
 
'@  The calculation will not be run.                          ',/,&
530
 
'@                                                            ',/,&
531
 
'@  Verify usvort.                                            ',/,&
532
 
'@                                                            ',/,&
533
 
'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@',/,&
534
 
'@                                                            ',/)
535
 
 
536
 
 3000 format(                                                           &
537
 
'                                                             ',/,&
538
 
' --  End reading the data file                               ',/)
539
 
 3100 format(                                                           &
540
 
'@                                                            ',/,&
541
 
'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@',/,&
542
 
'@                                                            ',/,&
543
 
'@ @@ WARNING: ABORT IN THE DATA SPECIFICATION                ',/,&
544
 
'@    ========                                                ',/,&
545
 
'@    U, K AND EPSILON ARE QUANTITIES WHICH MUST BE POSITIVE  ',/,&
546
 
'@    IN THE LOCAL FRAME OF THE INLET                         ',/,&
547
 
'@                                                            ',/,&
548
 
'@    VERIFY THE DATA FILE FOR THE INLET ',I10                 ,/,&
549
 
'@                                                            ',/,&
550
 
'@  The calculation will not be run.                          ',/,&
551
 
'@                                                            ',/,&
552
 
'@  Verify usvort.                                            ',/,&
553
 
'@                                                            ',/,&
554
 
'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@',/,&
555
 
'@                                                            ',/)
556
 
 3200 format(                                                           &
557
 
'@                                                            ',/,&
558
 
'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@',/,&
559
 
'@                                                            ',/,&
560
 
'@ @@ WARNING:       IN THE DATA SPECIFICATION                ',/,&
561
 
'@    ========                                                ',/,&
562
 
'@    THE MAX DIMENSIONS OF THE INLET ARE INCOMPATIBLE WITH   ',/,&
563
 
'@    THE ONES FROM THE DATA FILE                             ',/,&
564
 
'@                                                            ',/,&
565
 
'@    VERIFY THE DATA FILE FOR THE INLET ',I10                 ,/,&
566
 
'@                                                            ',/,&
567
 
'@  The calculation will be run.                              ',/,&
568
 
'@                                                            ',/,&
569
 
'@  Verify usvort.                                            ',/,&
570
 
'@                                                            ',/,&
571
 
'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@',/,&
572
 
'@                                                            ',/)
573
 
 
574
 
 4000 format(                                                           &
575
 
' --  End reading the restart file                            ',/)
576
 
 
577
 
 4500   format(                                                         &
578
 
'@                                                            ',/,&
579
 
'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@',/,&
580
 
'@                                                            ',/,&
581
 
'@ @@ WARNING:       IN THE DATA SPECIFICATION                ',/,&
582
 
'@    ========                                                ',/,&
583
 
'@  THE NUMBER OF VORTICES HAS CHANGED AT THE INLET ',I10      ,/,&
584
 
'@    NVORT WAS PREVIOUSLY ',I10                               ,/,&
585
 
'@    AT THE INLET ',I10                                       ,/,&
586
 
'@    IT IS CURRENTLY ',I10                                    ,/,&
587
 
'@                                                            ',/,&
588
 
'@  THE METHOD IS RE-INITIALIZED AT THIS INLET                ',/,&
589
 
'@                                                            ',/,&
590
 
'@  The calculation will be run.                              ',/,&
591
 
'@                                                            ',/,&
592
 
'@  Verify usvort.                                            ',/,&
593
 
'@                                                            ',/,&
594
 
'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@',/,&
595
 
'@                                                            ',/)
596
 
 
597
 
 100  format(i10)
598
 
 200  format(5e13.5)
599
 
 
600
 
#endif
601
 
 
602
 
return
603
 
end subroutine