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

« back to all changes in this revision

Viewing changes to src/lagr/enslag.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 enslag &
29
24
!================
30
25
 
31
 
 ( idbia0 , idbra0 ,                                              &
32
 
   nbpmax , nvp    , nvp1   , nvep   , nivep  ,                   &
 
26
 ( nbpmax , nvp    , nvp1   , nvep   , nivep  ,                   &
33
27
   nfin   , iforce ,                                              &
34
28
   itepa  ,                                                       &
35
 
   ettp   , tepa   , ra)
 
29
   ettp   , tepa   )
36
30
 
37
31
!===============================================================================
38
32
! FONCTION :
60
54
!__________________.____._____.________________________________________________.
61
55
! name             !type!mode ! role                                           !
62
56
!__________________!____!_____!________________________________________________!
63
 
! idbia0           ! i  ! <-- ! number of first free position in ia            !
64
 
! idbra0           ! i  ! <-- ! number of first free position in ra            !
65
57
! nbpmax           ! e  ! <-- ! nombre max de particulies autorise             !
66
58
! nvp              ! e  ! <-- ! nombre de variables particulaires              !
67
59
! nvp1             ! e  ! <-- ! nvp sans position, vfluide, vpart              !
72
64
! iforce           ! e  ! <-- ! force l'ecriture si = numero de la             !
73
65
!                  !    !     !   particule courante                           !
74
66
! itepa            ! te ! <-- ! info particulaires (entiers)                   !
75
 
! (nbpmax,nivep    !    !     !   (cellule de la particule,...)                !
 
67
! (nbpmax, nivep   !    !     !   (cellule de la particule, ...)               !
76
68
! ettp             ! tr ! <-- ! tableaux des variables liees                   !
77
 
!  (nbpmax,nvp)    !    !     !   aux particules                               !
 
69
!  (nbpmax, nvp)   !    !     !   aux particules                               !
78
70
!                  !    !     !   etape courante ou precedente                 !
79
71
! tepa             ! tr ! <-- ! info particulaires (reels)                     !
80
 
! (nbpmax,nvep)    !    !     !   (poids statistiques,...)                     !
 
72
! (nbpmax, nvep)   !    !     !   (poids statistiques, ...)                    !
81
73
!__________________!____!_____!________________________________________________!
82
74
 
83
75
!     TYPE : E (ENTIER), R (REEL), A (ALPHANUMERIQUE), T (TABLEAU)
84
76
!            L (LOGIQUE)   .. ET TYPES COMPOSES (EX : TR TABLEAU REEL)
85
77
!     MODE : <-- donnee, --> resultat, <-> Donnee modifiee
86
78
!            --- tableau de travail
87
 
 
88
79
!===============================================================================
89
80
 
 
81
!==============================================================================
 
82
! Module files
 
83
!==============================================================================
 
84
 
 
85
use paramx
 
86
use entsor
 
87
use lagpar
 
88
use lagran
 
89
 
 
90
!==============================================================================
 
91
 
90
92
implicit none
91
93
 
92
 
!==============================================================================
93
 
! Common blocks
94
 
!==============================================================================
95
 
 
96
 
include "paramx.h"
97
 
include "entsor.h"
98
 
include "lagpar.h"
99
 
include "lagran.h"
100
 
 
101
 
!==============================================================================
102
 
 
103
94
! Arguments
104
95
 
105
 
integer          idbia0 , idbra0
106
96
integer          nbpmax , nvp    , nvp1   , nvep  , nivep
107
97
integer          nfin   , iforce
108
 
integer          itepa(nbpmax,nivep)
109
 
double precision ettp(nbpmax,nvp) , tepa(nbpmax,nvep)
110
 
double precision ra(*)
 
98
integer          itepa(nbpmax, nivep)
 
99
double precision ettp(nbpmax, nvp) , tepa(nbpmax, nvep)
111
100
 
112
101
! Local variables
113
102
 
114
 
integer          idebia , idebra
115
103
integer          nl , np
116
104
 
117
105
integer          numl
118
106
integer          nume(nliste)
119
107
integer          ii1 , ii2 , lpos , nlmax , ios
120
108
integer          npt , ipt , lmax
121
 
integer          ix,iy,iz,ii
 
109
integer          ix, iy, iz, ii
122
110
integer          iu1l , iv1l  , iw1l
123
111
integer          iu2l , iv2l  , iw2l
124
112
integer          itpl , idml  , itel  , impl
125
113
integer          ihpl , idckl , imchl , imckl
126
 
integer          ifinia, ifinra
 
114
integer          nvpst
127
115
 
128
116
double precision xpl , ypl , zpl
129
117
double precision u1l , v1l , w1l
130
118
double precision u2l , v2l , w2l
131
119
double precision tpl , dml , tel , mpl
132
120
double precision hpl , dckl , mchl , mckl
 
121
 
 
122
double precision, allocatable, dimension(:,:) :: rwork
 
123
 
133
124
character        fich*80
134
125
character        name*80
135
126
 
143
134
! -1.  GESTION MEMOIRE
144
135
!===============================================================================
145
136
 
146
 
idebia = idbia0
147
 
idebra = idbra0
 
137
! Initialize variables to avoid compiler warnings
 
138
 
 
139
iu1l = 0
 
140
iv1l = 0
 
141
iw1l = 0
 
142
iu2l = 0
 
143
iv2l = 0
 
144
iw2l = 0
 
145
itpl = 0
 
146
idml = 0
 
147
impl = 0
 
148
itel = 0
 
149
ihpl = 0
 
150
idckl = 0
 
151
imchl = 0
 
152
imckl = 0
148
153
 
149
154
!===============================================================================
150
155
! 0. INITIALISATIONS
162
167
 
163
168
if (ipass.eq.1) then
164
169
 
165
 
  OPEN (IMPLA3,FILE='SCRATCH3.lag',                               &
166
 
        STATUS='UNKNOWN',FORM='UNFORMATTED',                      &
167
 
        ACCESS='SEQUENTIAL')
 
170
  open(impla3, file='scratch3.lag',                               &
 
171
       status='unknown', form='unformatted', access='sequential')
168
172
 
169
 
  do nl = 1,nbvis
 
173
  do nl = 1, nbvis
170
174
    nplist(nl) = 0
171
175
    list0(nl) = liste(nl)
172
176
  enddo
178
182
!    POUR CHAQUE PARTICULE A VISUALISER SUIVANT LA FREQUENCE
179
183
!===============================================================================
180
184
 
181
 
if ((mod(ipass-1,nvisla).eq.0 .or. iforce.gt.0)                   &
182
 
   .and. nfin.eq.0) then
183
 
 
184
 
 
185
 
  do nl = 1,nbvis
 
185
if ((mod(ipass-1, nvisla).eq.0 .or. iforce.gt.0) .and. nfin.eq.0) then
 
186
 
 
187
  do nl = 1, nbvis
186
188
 
187
189
    np = liste(nl)
188
190
 
189
 
    if ( (np.ge.1 .and. iforce.eq.0 ) .or.                        &
190
 
                       (iforce.eq.np)      ) then
191
 
 
192
 
! sortie du domaine ?
193
 
      if (itepa(np,jisor).gt.0) then
194
 
 
195
 
!--->incrementation du nombre d'enregistrement pour la particule NP :
 
191
    if ((np.ge.1 .and. iforce.eq.0) .or. (iforce.eq.np)) then
 
192
 
 
193
      ! sortie du domaine ?
 
194
      if (itepa(np, jisor).gt.0) then
 
195
 
 
196
        !--->incrementation du nombre d'enregistrement pour la particule NP :
196
197
        nplist(nl) = nplist(nl)+1
197
198
 
198
199
        if (nplist(nl).gt.nlmax) nlmax = nplist(nl)
199
200
 
200
 
!--->numero de liste :
 
201
        !--->numero de liste :
201
202
        write(impla3) nl
202
203
 
203
 
!--->coordonnees de la particule NP :
204
 
        write(impla3) ettp(np,jxp), ettp(np,jyp), ettp(np,jzp)
 
204
        !--->coordonnees de la particule NP :
 
205
        write(impla3) ettp(np, jxp), ettp(np, jyp), ettp(np, jzp)
205
206
 
206
 
!--->vitesse du fluide vu :
 
207
        !--->vitesse du fluide vu :
207
208
        if (ivisv1.eq.1) then
208
 
          write(impla3) ettp(np,juf), ettp(np,jvf), ettp(np,jwf)
 
209
          write(impla3) ettp(np, juf), ettp(np, jvf), ettp(np, jwf)
209
210
        endif
210
211
 
211
 
!--->vitesse de la particule :
 
212
        !--->vitesse de la particule :
212
213
        if (ivisv2.eq.1) then
213
 
          write(impla3) ettp(np,jup), ettp(np,jvp), ettp(np,jwp)
 
214
          write(impla3) ettp(np, jup), ettp(np, jvp), ettp(np, jwp)
214
215
        endif
215
216
 
216
 
!--->temps de sejour :
 
217
        !--->temps de sejour :
217
218
        if (ivistp.eq.1) then
218
 
          write(impla3) tepa(np,jrtsp)
 
219
          write(impla3) tepa(np, jrtsp)
219
220
        endif
220
221
 
221
 
!--->diametre :
 
222
        !--->diametre :
222
223
        if (ivisdm.eq.1) then
223
 
            write(impla3) ettp(np,jdp)
 
224
            write(impla3) ettp(np, jdp)
224
225
        endif
225
226
 
226
 
!--->masse :
 
227
        !--->masse :
227
228
        if (ivismp.eq.1) then
228
 
          write(impla3) ettp(np,jmp)
 
229
          write(impla3) ettp(np, jmp)
229
230
        endif
230
231
 
231
 
!--->temperature :
 
232
        !--->temperature :
232
233
        if (iviste.eq.1) then
233
 
          write(impla3) ettp(np,jtp)
 
234
          write(impla3) ettp(np, jtp)
234
235
        endif
235
236
 
236
 
!--->Specifique charbon :
237
 
!        Temperature
 
237
        !--->Specifique charbon :
 
238
        ! Temperature
238
239
        if (ivishp.eq.1) then
239
 
          write(impla3) ettp(np,jhp)
 
240
          write(impla3) ettp(np, jhp)
240
241
        endif
241
 
!        Diametre du coeur retrecisant
 
242
        ! Diametre du coeur retrecisant
242
243
        if (ivisdk.eq.1) then
243
 
          write(impla3) tepa(np,jrdck)
 
244
          write(impla3) tepa(np, jrdck)
244
245
        endif
245
 
!        Masse charbon reactif
 
246
        ! Masse charbon reactif
246
247
        if (ivisch.eq.1) then
247
 
          write(impla3) ettp(np,jmch)
 
248
          write(impla3) ettp(np, jmch)
248
249
        endif
249
 
!        Masse de coke
 
250
        ! Masse de coke
250
251
        if (ivisck.eq.1) then
251
 
          write(impla3) ettp(np,jmck)
 
252
          write(impla3) ettp(np, jmck)
252
253
        endif
253
254
 
254
255
      endif
257
258
 
258
259
  enddo
259
260
 
260
 
 
261
261
endif
262
262
 
263
263
!===============================================================================
269
269
  NAME = ' '
270
270
  NAME = 'trajectoire'
271
271
 
272
 
!  0) ouverture du fichier .ensight.CASE :
 
272
  !  0) ouverture du fichier .ensight.CASE :
273
273
 
274
274
  fich = name
275
 
  call verlon ( fich, ii1, ii2, lpos )
276
 
  FICH(II2+1:II2+14) = '.ensight.CASE'
 
275
  call verlon(fich, ii1, ii2, lpos)
 
276
  fich(ii2+1:ii2+14) = '.ensight.CASE'
277
277
  ii2 = ii2 + 14
278
 
  open ( unit=impla2, file=fich (ii1:ii2),                        &
279
 
         STATUS='UNKNOWN', FORM='FORMATTED',                      &
280
 
         ACCESS='SEQUENTIAL', IOSTAT=IOS, ERR=99 )
281
 
  rewind ( unit=impla2,err=99 )
 
278
  open(unit=impla2, file=fich (ii1:ii2),                        &
 
279
       status='unknown', form='formatted', access='sequential', &
 
280
       iostat=ios, err=99)
 
281
  rewind(unit=impla2, err=99)
282
282
 
283
283
  rewind(impla2)
284
 
  write(impla2,5010)
285
 
  write(impla2,5011)
286
 
  write(impla2,5012)
 
284
  write(impla2, 5010)
 
285
  write(impla2, 5011)
 
286
  write(impla2, 5012)
287
287
 
288
 
!  1) ouverture du fichier .ensight.geom + entete fichier case(suite)
 
288
  !  1) ouverture du fichier .ensight.geom + entete fichier case(suite)
289
289
 
290
290
  fich = name
291
 
  call verlon ( fich, ii1, ii2, lpos )
292
 
  FICH(II2+1:II2+13) = '.ensight.geom'
 
291
  call verlon(fich, ii1, ii2, lpos)
 
292
  fich(ii2+1:ii2+13) = '.ensight.geom'
293
293
  ii2 = ii2 + 13
294
294
 
295
 
  write(impla2,5013) fich (ii1:ii2)
296
 
  write(impla2,5014)
297
 
 
298
 
  open ( unit=impla1, file=fich (ii1:ii2),                        &
299
 
         STATUS='UNKNOWN', FORM='FORMATTED',                      &
300
 
         ACCESS='SEQUENTIAL', IOSTAT=IOS, ERR=99 )
301
 
 
302
 
  rewind ( unit=impla1,err=99 )
303
 
 
304
 
!  2) ouverture du fichier .vitflu + entete fichier case(suite)
 
295
  write(impla2, 5013) fich (ii1:ii2)
 
296
  write(impla2, 5014)
 
297
 
 
298
  open(unit=impla1, file=fich (ii1:ii2),                        &
 
299
       status='unknown', form='formatted', access='sequential', &
 
300
       iostat=ios, err=99)
 
301
 
 
302
  rewind(unit=impla1, err=99)
 
303
 
 
304
  !  2) ouverture du fichier .vitflu + entete fichier case(suite)
305
305
 
306
306
  if (ivisv1.eq.1) then
307
307
    fich = name
308
 
    call verlon ( fich, ii1, ii2, lpos )
309
 
    FICH(II2+1:II2+7) = '.vitflu'
 
308
    call verlon(fich, ii1, ii2, lpos)
 
309
    fich(ii2+1:ii2+7) = '.vitflu'
310
310
    ii2 = ii2 + 7
311
 
    open ( unit=impla5(1), file=fich (ii1:ii2),                   &
312
 
           STATUS='UNKNOWN', FORM='FORMATTED',                    &
313
 
           ACCESS='SEQUENTIAL', IOSTAT=IOS, ERR=99 )
314
 
    rewind ( unit=impla5(1),err=99 )
 
311
    open(unit=impla5(1), file=fich (ii1:ii2),                    &
 
312
        status='unknown', form='formatted', access='sequential', &
 
313
        iostat=ios, err=99)
 
314
    rewind(unit=impla5(1), err=99)
315
315
 
316
 
    write(impla2,5015) fich (ii1:ii2)
 
316
    write(impla2, 5015) fich (ii1:ii2)
317
317
 
318
318
  endif
319
319
 
320
 
!  3) ouverture du fichier .vitpar + entete fichier case(suite)
 
320
  !  3) ouverture du fichier .vitpar + entete fichier case(suite)
321
321
 
322
322
  if (ivisv2.eq.1) then
323
323
    fich = name
324
 
    call verlon ( fich, ii1, ii2, lpos )
325
 
    FICH(II2+1:II2+7) = '.vitpar'
 
324
    call verlon(fich, ii1, ii2, lpos)
 
325
    fich(ii2+1:ii2+7) = '.vitpar'
326
326
    ii2 = ii2 + 7
327
 
    open ( unit=impla5(2), file=fich (ii1:ii2),                   &
328
 
           STATUS='UNKNOWN', FORM='FORMATTED',                    &
329
 
           ACCESS='SEQUENTIAL', IOSTAT=IOS, ERR=99 )
330
 
    rewind ( unit=impla5(2),err=99 )
 
327
    open(unit=impla5(2), file=fich (ii1:ii2),                    &
 
328
         status='unknown', form='formatted', access='sequential', &
 
329
         iostat=ios, err=99)
 
330
    rewind(unit=impla5(2), err=99)
331
331
 
332
 
    write(impla2,5016) fich (ii1:ii2)
 
332
    write(impla2, 5016) fich (ii1:ii2)
333
333
 
334
334
  endif
335
335
 
337
337
 
338
338
  if (ivistp.eq.1) then
339
339
    fich = name
340
 
    call verlon ( fich, ii1, ii2, lpos )
341
 
    FICH(II2+1:II2+7) = '.tpssej'
 
340
    call verlon(fich, ii1, ii2, lpos)
 
341
    fich(ii2+1:ii2+7) = '.tpssej'
342
342
    ii2 = ii2 + 7
343
 
    open ( unit=impla5(3), file=fich (ii1:ii2),                   &
344
 
           STATUS='UNKNOWN', FORM='FORMATTED',                    &
345
 
           ACCESS='SEQUENTIAL', IOSTAT=IOS, ERR=99 )
346
 
    rewind ( unit=impla5(3),err=99 )
 
343
    open(unit=impla5(3), file=fich (ii1:ii2),                     &
 
344
         status='unknown', form='formatted', access='sequential', &
 
345
         iostat=ios, err=99)
 
346
    rewind(unit=impla5(3), err=99)
347
347
 
348
 
    write(impla2,5017) fich (ii1:ii2)
 
348
    write(impla2, 5017) fich (ii1:ii2)
349
349
 
350
350
  endif
351
351
 
353
353
 
354
354
  if (ivisdm.eq.1) then
355
355
    fich = name
356
 
    call verlon ( fich, ii1, ii2, lpos )
357
 
    FICH(II2+1:II2+7) = '.diamet'
 
356
    call verlon(fich, ii1, ii2, lpos)
 
357
    fich(ii2+1:ii2+7) = '.diamet'
358
358
    ii2 = ii2 + 7
359
 
    open ( unit=impla5(4), file=fich (ii1:ii2),                   &
360
 
           STATUS='UNKNOWN', FORM='FORMATTED',                    &
361
 
           ACCESS='SEQUENTIAL', IOSTAT=IOS, ERR=99 )
362
 
    rewind ( unit=impla5(4),err=99 )
 
359
    open(unit=impla5(4), file=fich (ii1:ii2),                     &
 
360
         status='unknown', form='formatted', access='sequential', &
 
361
         iostat=ios, err=99)
 
362
    rewind(unit=impla5(4), err=99)
363
363
 
364
 
    write(impla2,5018) fich (ii1:ii2)
 
364
    write(impla2, 5018) fich (ii1:ii2)
365
365
 
366
366
  endif
367
367
 
369
369
 
370
370
  if (ivismp.eq.1) then
371
371
    fich = name
372
 
    call verlon ( fich, ii1, ii2, lpos )
373
 
    FICH(II2+1:II2+7) = '.masse'
 
372
    call verlon(fich, ii1, ii2, lpos)
 
373
    fich(ii2+1:ii2+7) = '.masse'
374
374
    ii2 = ii2 + 7
375
 
    open ( unit=impla5(5), file=fich (ii1:ii2),                   &
376
 
           STATUS='UNKNOWN', FORM='FORMATTED',                    &
377
 
           ACCESS='SEQUENTIAL', IOSTAT=IOS, ERR=99 )
378
 
    rewind ( unit=impla5(5),err=99 )
 
375
    open(unit=impla5(5), file=fich (ii1:ii2),                     &
 
376
         status='unknown', form='formatted', access='sequential', &
 
377
         iostat=ios, err=99)
 
378
    rewind(unit=impla5(5), err=99)
379
379
 
380
 
    write(impla2,5019) fich (ii1:ii2)
 
380
    write(impla2, 5019) fich (ii1:ii2)
381
381
 
382
382
  endif
383
383
 
385
385
 
386
386
  if (iviste.eq.1) then
387
387
    fich = name
388
 
    call verlon ( fich, ii1, ii2, lpos )
389
 
    FICH(II2+1:II2+7) = '.temper'
 
388
    call verlon(fich, ii1, ii2, lpos)
 
389
    fich(ii2+1:ii2+7) = '.temper'
390
390
    ii2 = ii2 + 7
391
 
    open ( unit=impla5(6), file=fich (ii1:ii2),                   &
392
 
           STATUS='UNKNOWN', FORM='FORMATTED',                    &
393
 
           ACCESS='SEQUENTIAL', IOSTAT=IOS, ERR=99 )
394
 
    rewind ( unit=impla5(6),err=99 )
 
391
    open(unit=impla5(6), file=fich (ii1:ii2),                     &
 
392
         status='unknown', form='formatted', access='sequential', &
 
393
         iostat=ios, err=99)
 
394
    rewind(unit=impla5(6), err=99)
395
395
 
396
 
    write(impla2,5020) fich (ii1:ii2)
 
396
    write(impla2, 5020) fich (ii1:ii2)
397
397
 
398
398
  endif
399
399
 
401
401
 
402
402
  if (ivishp.eq.1) then
403
403
    fich = name
404
 
    call verlon ( fich, ii1, ii2, lpos )
405
 
    FICH(II2+1:II2+7) = '.tempch'
 
404
    call verlon(fich, ii1, ii2, lpos)
 
405
    fich(ii2+1:ii2+7) = '.tempch'
406
406
    ii2 = ii2 + 7
407
 
    open ( unit=impla5(7), file=fich (ii1:ii2),                   &
408
 
           STATUS='UNKNOWN', FORM='FORMATTED',                    &
409
 
           ACCESS='SEQUENTIAL', IOSTAT=IOS, ERR=99 )
410
 
    rewind ( unit=impla5(7),err=99 )
 
407
    open(unit=impla5(7), file=fich (ii1:ii2),                     &
 
408
         status='unknown', form='formatted', access='sequential', &
 
409
         iostat=ios, err=99)
 
410
    rewind(unit=impla5(7), err=99)
411
411
 
412
 
    write(impla2,5021) fich (ii1:ii2)
 
412
    write(impla2, 5021) fich (ii1:ii2)
413
413
 
414
414
  endif
415
415
 
417
417
 
418
418
  if (ivisdk.eq.1) then
419
419
    fich = name
420
 
    call verlon ( fich, ii1, ii2, lpos )
421
 
    FICH(II2+1:II2+7) = '.dck'
 
420
    call verlon(fich, ii1, ii2, lpos)
 
421
    fich(ii2+1:ii2+7) = '.dck'
422
422
    ii2 = ii2 + 7
423
 
    open ( unit=impla5(8), file=fich (ii1:ii2),                   &
424
 
           STATUS='UNKNOWN', FORM='FORMATTED',                    &
425
 
           ACCESS='SEQUENTIAL', IOSTAT=IOS, ERR=99 )
426
 
    rewind ( unit=impla5(8),err=99 )
 
423
    open(unit=impla5(8), file=fich (ii1:ii2),                     &
 
424
         status='unknown', form='formatted', access='sequential', &
 
425
         iostat=ios, err=99)
 
426
    rewind(unit=impla5(8), err=99)
427
427
 
428
 
    write(impla2,5022) fich (ii1:ii2)
 
428
    write(impla2, 5022) fich (ii1:ii2)
429
429
 
430
430
  endif
431
431
 
433
433
 
434
434
  if (ivisch.eq.1) then
435
435
    fich = name
436
 
    call verlon ( fich, ii1, ii2, lpos )
437
 
    FICH(II2+1:II2+7) = '.mch'
 
436
    call verlon(fich, ii1, ii2, lpos)
 
437
    fich(ii2+1:ii2+7) = '.mch'
438
438
    ii2 = ii2 + 7
439
 
    open ( unit=impla5(9), file=fich (ii1:ii2),                   &
440
 
           STATUS='UNKNOWN', FORM='FORMATTED',                    &
441
 
           ACCESS='SEQUENTIAL', IOSTAT=IOS, ERR=99 )
442
 
    rewind ( unit=impla5(9),err=99 )
 
439
    open(unit=impla5(9), file=fich (ii1:ii2),                     &
 
440
         status='unknown', form='formatted', access='sequential', &
 
441
         iostat=ios, err=99)
 
442
    rewind(unit=impla5(9), err=99)
443
443
 
444
 
    write(impla2,5023) fich (ii1:ii2)
 
444
    write(impla2, 5023) fich (ii1:ii2)
445
445
 
446
446
  endif
447
447
 
449
449
 
450
450
  if (ivisck.eq.1) then
451
451
    fich = name
452
 
    call verlon ( fich, ii1, ii2, lpos )
453
 
    FICH(II2+1:II2+7) = '.mck'
 
452
    call verlon(fich, ii1, ii2, lpos)
 
453
    fich(ii2+1:ii2+7) = '.mck'
454
454
    ii2 = ii2 + 7
455
 
    open ( unit=impla5(10), file=fich (ii1:ii2),                  &
456
 
           STATUS='UNKNOWN', FORM='FORMATTED',                    &
457
 
           ACCESS='SEQUENTIAL', IOSTAT=IOS, ERR=99 )
458
 
    rewind ( unit=impla5(10),err=99 )
 
455
    open(unit=impla5(10), file=fich (ii1:ii2),                    &
 
456
         status='unknown', form='formatted', access='sequential', &
 
457
         iostat=ios, err=99)
 
458
    rewind(unit=impla5(10), err=99)
459
459
 
460
 
    write(impla2,5024) fich (ii1:ii2)
 
460
    write(impla2, 5024) fich (ii1:ii2)
461
461
 
462
462
  endif
463
463
 
472
472
  npt = 0
473
473
  nlmax = 0
474
474
  lmax = 0
475
 
  do nl = 1,nbvis
 
475
  do nl = 1, nbvis
476
476
    npt = npt + nplist(nl)
477
 
    lmax = max(lmax,nplist(nl))
 
477
    lmax = max(lmax, nplist(nl))
478
478
    if (nplist(nl).gt.nlmax) nlmax = nplist(nl)
479
479
    nume(nl) = 0
480
480
  enddo
481
481
 
482
482
! 2) Allocation Memoire
483
483
 
484
 
  ifinia = idebia
485
 
  ix     = idebra
486
 
  iy     = ix+lmax
487
 
  iz     = iy+lmax
488
 
  ifinra = iz +lmax
 
484
  ! First, count the number of variables in post-processing
 
485
 
 
486
  nvpst = 1
 
487
  ix    = nvpst
 
488
  nvpst = nvpst + 1
 
489
  iy    = nvpst
 
490
  nvpst = nvpst + 1
 
491
  iz    = nvpst
489
492
 
490
493
  if (ivisv1.eq.1) then
491
 
    iu1l   = ifinra
492
 
    iv1l   = iu1l  +lmax
493
 
    iw1l   = iv1l  +lmax
494
 
    ifinra = iw1l  +lmax
 
494
    nvpst = nvpst + 1
 
495
    iu1l   = nvpst
 
496
    nvpst = nvpst + 1
 
497
    iv1l   = nvpst
 
498
    nvpst = nvpst + 1
 
499
    iw1l   = nvpst
495
500
  endif
496
501
  if (ivisv2.eq.1) then
497
 
    iu2l   = ifinra
498
 
    iv2l   = iu2l  +lmax
499
 
    iw2l   = iv2l  +lmax
500
 
    ifinra = iw2l  +lmax
 
502
    nvpst = nvpst + 1
 
503
    iu2l   = nvpst
 
504
    nvpst = nvpst + 1
 
505
    iv2l   = nvpst
 
506
    nvpst = nvpst + 1
 
507
    iw2l   = nvpst
501
508
  endif
502
509
  if (ivistp.eq.1) then
503
 
    itpl = ifinra
504
 
    ifinra = itpl +lmax
 
510
    nvpst = nvpst + 1
 
511
    itpl = nvpst
505
512
  endif
506
513
  if (ivisdm.eq.1) then
507
 
    idml = ifinra
508
 
    ifinra = idml +lmax
 
514
    nvpst = nvpst + 1
 
515
    idml = nvpst
509
516
  endif
510
517
  if (ivismp.eq.1) then
511
 
    impl = ifinra
512
 
    ifinra = impl +lmax
 
518
    nvpst = nvpst + 1
 
519
    impl = nvpst
513
520
  endif
514
521
  if (iviste.eq.1) then
515
 
    itel = ifinra
516
 
    ifinra = itel +lmax
 
522
    nvpst = nvpst + 1
 
523
    itel = nvpst
517
524
  endif
518
525
  if (ivishp.eq.1) then
519
 
    ihpl = ifinra
520
 
    ifinra = ihpl +lmax
 
526
    nvpst = nvpst + 1
 
527
    ihpl = nvpst
521
528
  endif
522
529
  if (ivisdk.eq.1) then
523
 
    idckl= ifinra
524
 
    ifinra = idckl +lmax
 
530
    nvpst = nvpst + 1
 
531
    idckl= nvpst
525
532
  endif
526
533
  if (ivisch.eq.1) then
527
 
    imchl = ifinra
528
 
    ifinra = imchl +lmax
 
534
    nvpst = nvpst + 1
 
535
    imchl = nvpst
529
536
  endif
530
537
  if (ivisck.eq.1) then
531
 
    imckl = ifinra
532
 
    ifinra = imckl +lmax
 
538
    nvpst = nvpst + 1
 
539
    imckl = nvpst
533
540
  endif
534
541
 
535
 
  CALL RASIZE('ENSLAG',IFINRA)
536
 
  !==========
 
542
  ! Second, allocate a global work array of dimensions "lmax*nvpst"
 
543
 
 
544
  allocate(rwork(lmax,nvpst))
537
545
 
538
546
! 3) ON REMPLIT LES ENTETES DES FICHIERS : geo + variable
539
547
 
540
548
  rewind(impla1)
541
549
 
542
 
  write(impla1,3000)
543
 
  write(impla1,3001)
544
 
  write(impla1,3002)
545
 
  write(impla1,3003)
 
550
  write(impla1, 3000)
 
551
  write(impla1, 3001)
 
552
  write(impla1, 3002)
 
553
  write(impla1, 3003)
546
554
 
547
555
  if (ivisv1.eq.1) then
548
556
    rewind(impla5(1))
549
 
    write(impla5(1),4000)
 
557
    write(impla5(1), 4000)
550
558
  endif
551
559
 
552
560
  if (ivisv2.eq.1) then
553
561
    rewind(impla5(2))
554
 
    write(impla5(2),4001)
 
562
    write(impla5(2), 4001)
555
563
  endif
556
564
 
557
565
  if (ivistp.eq.1) then
558
566
    rewind(impla5(3))
559
 
    write(impla5(3),4002)
 
567
    write(impla5(3), 4002)
560
568
  endif
561
569
 
562
570
  if (ivisdm.eq.1) then
563
571
    rewind(impla5(4))
564
 
    write(impla5(4),4003)
 
572
    write(impla5(4), 4003)
565
573
  endif
566
574
 
567
575
  if (ivismp.eq.1) then
568
576
    rewind(impla5(5))
569
 
    write(impla5(5),4004)
 
577
    write(impla5(5), 4004)
570
578
  endif
571
579
 
572
580
  if (iviste.eq.1) then
573
581
    rewind(impla5(6))
574
 
    write(impla5(6),4005)
 
582
    write(impla5(6), 4005)
575
583
  endif
576
584
 
577
585
  if (ivishp.eq.1) then
578
586
    rewind(impla5(7))
579
 
    write(impla5(7),4006)
 
587
    write(impla5(7), 4006)
580
588
  endif
581
589
 
582
590
  if (ivisdk.eq.1) then
583
591
    rewind(impla5(8))
584
 
    write(impla5(8),4007)
 
592
    write(impla5(8), 4007)
585
593
  endif
586
594
 
587
595
  if (ivisch.eq.1) then
588
596
    rewind(impla5(9))
589
 
    write(impla5(9),4008)
 
597
    write(impla5(9), 4008)
590
598
 endif
591
599
 
592
600
  if (ivisck.eq.1) then
593
601
    rewind(impla5(10))
594
 
    write(impla5(10),4009)
 
602
    write(impla5(10), 4009)
595
603
  endif
596
604
 
597
 
  do nl = 1,nbvis
 
605
  do nl = 1, nbvis
598
606
 
599
607
    np = liste(nl)
600
608
 
601
 
    if (itepa(np,jisor).gt.0) then
 
609
    if (itepa(np, jisor).gt.0) then
602
610
 
603
611
      rewind(impla3)
604
612
 
605
613
      ipt = 0
606
 
      do ii=1,npt
 
614
      do ii=1, npt
607
615
 
608
616
        read(impla3) numl
609
 
        read(impla3) xpl,ypl,zpl
610
 
        if (ivisv1.eq.1) read(impla3) u1l,v1l,w1l
611
 
        if (ivisv2.eq.1) read(impla3) u2l,v2l,w2l
 
617
        read(impla3) xpl, ypl, zpl
 
618
        if (ivisv1.eq.1) read(impla3) u1l, v1l, w1l
 
619
        if (ivisv2.eq.1) read(impla3) u2l, v2l, w2l
612
620
        if (ivistp.eq.1) read(impla3) tpl
613
621
        if (ivisdm.eq.1) read(impla3) dml
614
622
        if (ivismp.eq.1) read(impla3) mpl
618
626
        if (ivisch.eq.1) read(impla3) mchl
619
627
        if (ivisck.eq.1) read(impla3) mckl
620
628
 
621
 
        if (numl .eq. nl ) then
 
629
        if (numl .eq. nl) then
622
630
 
623
631
          ipt = ipt+1
624
632
 
625
 
          ra(ix+ipt-1) = xpl
626
 
          ra(iy+ipt-1) = ypl
627
 
          ra(iz+ipt-1) = zpl
 
633
          rwork(ipt,ix) = xpl
 
634
          rwork(ipt,iy) = ypl
 
635
          rwork(ipt,iz) = zpl
628
636
          if (ivisv1.eq.1) then
629
 
            ra(iu1l+ipt-1) = u1l
630
 
            ra(iv1l+ipt-1) = v1l
631
 
            ra(iw1l+ipt-1) = w1l
 
637
            rwork(ipt,iu1l) = u1l
 
638
            rwork(ipt,iv1l) = v1l
 
639
            rwork(ipt,iw1l) = w1l
632
640
          endif
633
641
          if (ivisv2.eq.1) then
634
 
            ra(iu2l+ipt-1) = u2l
635
 
            ra(iv2l+ipt-1) = v2l
636
 
            ra(iw2l+ipt-1) = w2l
 
642
            rwork(ipt,iu2l) = u2l
 
643
            rwork(ipt,iv2l) = v2l
 
644
            rwork(ipt,iw2l) = w2l
637
645
          endif
638
646
          if (ivistp.eq.1) then
639
 
            ra(itpl+ipt-1) = tpl
 
647
            rwork(ipt,itpl) = tpl
640
648
          endif
641
649
          if (ivisdm.eq.1) then
642
 
            ra(idml+ipt-1) = dml
 
650
            rwork(ipt,idml) = dml
643
651
          endif
644
652
          if (ivismp.eq.1) then
645
 
            ra(impl+ipt-1) = mpl
 
653
            rwork(ipt,impl) = mpl
646
654
          endif
647
655
          if (iviste.eq.1) then
648
 
            ra(itel+ipt-1) = tel
 
656
            rwork(ipt,itel) = tel
649
657
          endif
650
658
          if (ivishp.eq.1) then
651
 
            ra(ihpl+ipt-1) = hpl
 
659
            rwork(ipt,ihpl) = hpl
652
660
          endif
653
661
          if (ivisdk.eq.1) then
654
 
            ra(idckl+ipt-1) = dckl
 
662
            rwork(ipt,idckl) = dckl
655
663
          endif
656
664
          if (ivisch.eq.1) then
657
 
            ra(imchl+ipt-1) = mchl
 
665
            rwork(ipt,imchl) = mchl
658
666
          endif
659
667
          if (ivisck.eq.1) then
660
 
            ra(imckl+ipt-1) = mckl
 
668
            rwork(ipt,imckl) = mckl
661
669
          endif
662
670
 
663
671
        endif
665
673
 
666
674
!  Ecriture Fichier Geometrie
667
675
 
668
 
      write(impla1,3010)
669
 
      write(impla1,1010) nl
670
 
      write(impla1,3004) list0(nl)
671
 
      write(impla1,3005)
672
 
      write(impla1,1010) ipt
673
 
      do ii=1,ipt
674
 
        write(impla1,1030) ra(ix+ii-1)
675
 
      enddo
676
 
      do ii=1,ipt
677
 
        write(impla1,1030) ra(iy+ii-1)
678
 
      enddo
679
 
      do ii=1,ipt
680
 
        write(impla1,1030) ra(iz+ii-1)
681
 
      enddo
682
 
      write(impla1,3006)
 
676
      write(impla1, 3010)
 
677
      write(impla1, 1010) nl
 
678
      write(impla1, 3004) list0(nl)
 
679
      write(impla1, 3005)
 
680
      write(impla1, 1010) ipt
 
681
      do ii=1, ipt
 
682
        write(impla1, 1030) rwork(ii,ix)
 
683
      enddo
 
684
      do ii=1, ipt
 
685
        write(impla1, 1030) rwork(ii,iy)
 
686
      enddo
 
687
      do ii=1, ipt
 
688
        write(impla1, 1030) rwork(ii,iz)
 
689
      enddo
 
690
      write(impla1, 3006)
683
691
      if (ipt.eq.0) then
684
 
        write(impla1,1010) 0
 
692
        write(impla1, 1010) 0
685
693
      else
686
 
        write(impla1,1010) ipt-1
 
694
        write(impla1, 1010) ipt-1
687
695
      endif
688
 
      do ii=1,ipt-1
689
 
        write(impla1,1020) ii,ii+1
 
696
      do ii=1, ipt-1
 
697
        write(impla1, 1020) ii, ii+1
690
698
      enddo
691
699
 
692
700
!  Ecriture Fichiers Variables
693
701
 
694
702
      if (ivisv1.eq.1) then
695
703
 
696
 
        write(impla5(1),3010)
697
 
        write(impla5(1),1010) nl
698
 
        write(impla5(1),3005)
699
 
        do ii=1,ipt
700
 
          write(impla5(1),1030) ra(iu1l+ii-1)
701
 
        enddo
702
 
        do ii=1,ipt
703
 
          write(impla5(1),1030) ra(iv1l+ii-1)
704
 
        enddo
705
 
        do ii=1,ipt
706
 
          write(impla5(1),1030) ra(iw1l+ii-1)
 
704
        write(impla5(1), 3010)
 
705
        write(impla5(1), 1010) nl
 
706
        write(impla5(1), 3005)
 
707
        do ii=1, ipt
 
708
          write(impla5(1), 1030) rwork(ii,iu1l)
 
709
        enddo
 
710
        do ii=1, ipt
 
711
          write(impla5(1), 1030) rwork(ii,iv1l)
 
712
        enddo
 
713
        do ii=1, ipt
 
714
          write(impla5(1), 1030) rwork(ii,iw1l)
707
715
        enddo
708
716
      endif
709
717
 
710
718
      if (ivisv2.eq.1) then
711
 
        write(impla5(2),3010)
712
 
        write(impla5(2),1010) nl
713
 
        write(impla5(2),3005)
714
 
        do ii=1,ipt
715
 
          write(impla5(2),1030) ra(iu2l+ii-1)
716
 
        enddo
717
 
        do ii=1,ipt
718
 
          write(impla5(2),1030) ra(iv2l+ii-1)
719
 
        enddo
720
 
        do ii=1,ipt
721
 
          write(impla5(2),1030) ra(iw2l+ii-1)
 
719
        write(impla5(2), 3010)
 
720
        write(impla5(2), 1010) nl
 
721
        write(impla5(2), 3005)
 
722
        do ii=1, ipt
 
723
          write(impla5(2), 1030) rwork(ii,iu2l)
 
724
        enddo
 
725
        do ii=1, ipt
 
726
          write(impla5(2), 1030) rwork(ii,iv2l)
 
727
        enddo
 
728
        do ii=1, ipt
 
729
          write(impla5(2), 1030) rwork(ii,iw2l)
722
730
        enddo
723
731
      endif
724
732
 
725
733
      if (ivistp.eq.1) then
726
 
        write(impla5(3),3010)
727
 
        write(impla5(3),1010) nl
728
 
        write(impla5(3),3005)
729
 
        do ii=1,ipt
730
 
          write(impla5(3),1030) ra(itpl+ii-1)
 
734
        write(impla5(3), 3010)
 
735
        write(impla5(3), 1010) nl
 
736
        write(impla5(3), 3005)
 
737
        do ii=1, ipt
 
738
          write(impla5(3), 1030) rwork(ii,itpl)
731
739
        enddo
732
740
      endif
733
741
      if (ivisdm.eq.1) then
734
 
        write(impla5(4),3010)
735
 
        write(impla5(4),1010) nl
736
 
        write(impla5(4),3005)
737
 
        do ii=1,ipt
738
 
          write(impla5(4) ,1030) ra(idml+ii-1)
 
742
        write(impla5(4), 3010)
 
743
        write(impla5(4), 1010) nl
 
744
        write(impla5(4), 3005)
 
745
        do ii=1, ipt
 
746
          write(impla5(4), 1030) rwork(ii,idml)
739
747
        enddo
740
748
      endif
741
749
      if (ivismp.eq.1) then
742
 
        write(impla5(5),3010)
743
 
        write(impla5(5),1010) nl
744
 
        write(impla5(5),3005)
745
 
        do ii=1,ipt
746
 
          write(impla5(5),1030) ra(impl+ii-1)
 
750
        write(impla5(5), 3010)
 
751
        write(impla5(5), 1010) nl
 
752
        write(impla5(5), 3005)
 
753
        do ii=1, ipt
 
754
          write(impla5(5), 1030) rwork(ii,impl)
747
755
        enddo
748
756
      endif
749
757
      if (iviste.eq.1) then
750
 
        write(impla5(6),3010)
751
 
        write(impla5(6),1010) nl
752
 
        write(impla5(6),3005)
753
 
        do ii=1,ipt
754
 
          write(impla5(6),1030) ra(itel+ii-1)
 
758
        write(impla5(6), 3010)
 
759
        write(impla5(6), 1010) nl
 
760
        write(impla5(6), 3005)
 
761
        do ii=1, ipt
 
762
          write(impla5(6), 1030) rwork(ii,itel)
755
763
        enddo
756
764
      endif
757
765
      if (ivishp.eq.1) then
758
 
        write(impla5(7),3010)
759
 
        write(impla5(7),1010) nl
760
 
        write(impla5(7),3005)
761
 
        do ii=1,ipt
762
 
          write(impla5(7),1030) ra(ihpl+ii-1)
 
766
        write(impla5(7), 3010)
 
767
        write(impla5(7), 1010) nl
 
768
        write(impla5(7), 3005)
 
769
        do ii=1, ipt
 
770
          write(impla5(7), 1030) rwork(ii,ihpl)
763
771
        enddo
764
772
      endif
765
773
      if (ivisdk.eq.1) then
766
 
        write(impla5(8),3010)
767
 
        write(impla5(8),1010) nl
768
 
        write(impla5(8),3005)
769
 
        do ii=1,ipt
770
 
          write(impla5(8),1030) ra(idckl+ii-1)
 
774
        write(impla5(8), 3010)
 
775
        write(impla5(8), 1010) nl
 
776
        write(impla5(8), 3005)
 
777
        do ii=1, ipt
 
778
          write(impla5(8), 1030) rwork(ii,idckl)
771
779
        enddo
772
780
      endif
773
781
      if (ivisch.eq.1) then
774
 
        write(impla5(9),3010)
775
 
        write(impla5(9),1010) nl
776
 
        write(impla5(9),3005)
777
 
        do ii=1,ipt
778
 
          write(impla5(9),1030) ra(imchl+ii-1)
 
782
        write(impla5(9), 3010)
 
783
        write(impla5(9), 1010) nl
 
784
        write(impla5(9), 3005)
 
785
        do ii=1, ipt
 
786
          write(impla5(9), 1030) rwork(ii,imchl)
779
787
        enddo
780
788
      endif
781
789
      if (ivisck.eq.1) then
782
 
        write(impla5(10),3010)
783
 
        write(impla5(10),1010) nl
784
 
        write(impla5(10),3005)
785
 
        do ii=1,ipt
786
 
          write(impla5(10),1030) ra(imckl+ii-1)
 
790
        write(impla5(10), 3010)
 
791
        write(impla5(10), 1010) nl
 
792
        write(impla5(10), 3005)
 
793
        do ii=1, ipt
 
794
          write(impla5(10), 1030) rwork(ii,imckl)
787
795
        enddo
788
796
      endif
789
797
 
811
819
return
812
820
 
813
821
   99 continue
814
 
write (nfecra,9999) fich (ii1:ii2), ios
 
822
write (nfecra, 9999) fich (ii1:ii2), ios
815
823
call csexit(1)
816
824
 
817
825
!--------
819
827
!--------
820
828
 
821
829
 1010 format (i10)
822
 
 1020 format (i10,i10)
 
830
 1020 format (i10, i10)
823
831
 1030 format (e12.5)
824
832
 
825
833
 3000 format('geometrie trajectoire')
826
834
 3001 format('au format ensight6 : .case')
827
835
 3002 format('node id assign')
828
836
 3003 format('element id assign')
829
 
 3004 format('trajectoire',I10)
 
837
 3004 format('trajectoire', I10)
830
838
 3005 format('coordinates')
831
839
 3006 format('bar2')
832
840
 
846
854
 5010 format('FORMAT')
847
855
 5011 format('type: ensight gold')
848
856
 5012 format('GEOMETRY')
849
 
 5013 format('model: ',A)
 
857
 5013 format('model: ', A)
850
858
 5014 format('VARIABLE')
851
 
 5015 format('vector per node: vitesse_fluide_vu       ',A )
852
 
 5016 format('vector per node: vitesse_particules      ',A )
853
 
 5017 format('scalar per node: temps_de_sejour         ',A )
854
 
 5018 format('scalar per node: diametre                ',A )
855
 
 5019 format('scalar per node: masse                   ',A )
856
 
 5020 format('scalar per node: temperature             ',A )
857
 
 5021 format('scalar per node: temperature             ',A )
858
 
 5022 format('scalar per node: dck                     ',A )
859
 
 5023 format('scalar per node: mch                     ',A )
860
 
 5024 format('scalar per node: mck                     ',A )
 
859
 5015 format('vector per node: vitesse_fluide_vu       ', A)
 
860
 5016 format('vector per node: vitesse_particules      ', A)
 
861
 5017 format('scalar per node: temps_de_sejour         ', A)
 
862
 5018 format('scalar per node: diametre                ', A)
 
863
 5019 format('scalar per node: masse                   ', A)
 
864
 5020 format('scalar per node: temperature             ', A)
 
865
 5021 format('scalar per node: temperature             ', A)
 
866
 5022 format('scalar per node: dck                     ', A)
 
867
 5023 format('scalar per node: mch                     ', A)
 
868
 5024 format('scalar per node: mck                     ', A)
861
869
 
862
 
 9999 format(                                                           &
863
 
'@                                                            ',/,&
864
 
'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@',/,&
865
 
'@                                                            ',/,&
866
 
'@ @@ ATTENTION : ARRET A L''EXECUTION DU MODULE LAGRANGIEN   ',/,&
867
 
'@    =========                                               ',/,&
868
 
'@    ERREUR D''OUVERTURE SUR LE FICHIER : ',A                 ,/,&
869
 
'@    AVEC UN IOSTAT EGAL A : ',I6                             ,/,&
870
 
'@    (ENSLAG)                                                ',/,&
871
 
'@                                                            ',/,&
872
 
'@  Verifier les numero de fichiers utilises par le Lagrangien',/,&
873
 
'@                                                            ',/,&
874
 
'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@',/,&
875
 
'@                                                            ',/)
 
870
 9999 format(                                                       &
 
871
'@                                                            ', /, &
 
872
'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@', /, &
 
873
'@                                                            ', /, &
 
874
'@ @@ ATTENTION : ARRET A L''EXECUTION DU MODULE LAGRANGIEN   ', /, &
 
875
'@    =========                                               ', /, &
 
876
'@    ERREUR D''OUVERTURE SUR LE FICHIER : ', A                , /, &
 
877
'@    AVEC UN IOSTAT EGAL A : ', I6                            , /, &
 
878
'@    (ENSLAG)                                                ', /, &
 
879
'@                                                            ', /, &
 
880
'@  Verifier les numero de fichiers utilises par le Lagrangien', /, &
 
881
'@                                                            ', /, &
 
882
'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@', /, &
 
883
'@                                                            ', /)
876
884
 
877
885
!----
878
886
! FIN