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

« back to all changes in this revision

Viewing changes to src/base/armtps.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 armtps &
29
 
!================
30
 
 
31
 
 ( ntcabs , ntmabs )
32
 
 
33
 
!===============================================================================
34
 
 
35
 
! FONCTION :
36
 
! --------
37
 
!          ROUTINE PERMETTANT DE STOPPER LE CALCUL PROPREMENT SI
38
 
!            LE TEMPS RESTANT ALLOUE AU PROCESS EST INSUFFISANT
39
 
!            UNIQUEMENT POUR VPP ET CLUSTER LINUX
40
 
 
41
 
!-------------------------------------------------------------------------------
42
 
! Arguments
43
 
!__________________.____._____.________________________________________________.
44
 
! name             !type!mode ! role                                           !
45
 
!__________________!____!_____!________________________________________________!
46
 
! ntcabs           ! e  ! <-- ! numero absolu du pas de temps courant          !
47
 
! ntmabs           ! e  ! <-- ! numero absolu du pas de temps final            !
48
 
!__________________!____!_____!________________________________________________!
49
 
 
50
 
!     TYPE : E (ENTIER), R (REEL), A (ALPHANUMERIQUE), T (TABLEAU)
51
 
!            L (LOGIQUE)   .. ET TYPES COMPOSES (EX : TR TABLEAU REEL)
52
 
!     MODE : <-- donnee, --> resultat, <-> Donnee modifiee
53
 
!            --- tableau de travail
54
 
!===============================================================================
55
 
 
56
 
implicit none
57
 
 
58
 
!===============================================================================
59
 
! Common blocks
60
 
!===============================================================================
61
 
 
62
 
include "paramx.h"
63
 
include "entsor.h"
64
 
include "parall.h"
65
 
 
66
 
!===============================================================================
67
 
 
68
 
! Arguments
69
 
 
70
 
integer          ntcabs , ntmabs
71
 
 
72
 
! Local variables
73
 
 
74
 
integer irangs, lng, itmp(1), itlim
75
 
integer imetho
76
 
data    imetho /-1/
77
 
save    imetho
78
 
 
79
 
integer ntcab0
80
 
save    ntcab0
81
 
double precision trest0, trestp, tcpupr
82
 
save             trest0, trestp, tcpupr
83
 
 
84
 
double precision tmoy00, titpre, trestc, tmoyit, alpha, titsup
85
 
double precision tmarge, aa, bb, cc, tmamin
86
 
double precision tcpuco
87
 
double precision tresmn, titsmx
88
 
 
89
 
!===============================================================================
90
 
 
91
 
!     La variable IMETHO indique si l'on a utilise avec succes
92
 
!     TREMAIN (1), TCPUMX (2) pour determiner le temps CPU limite,
93
 
!     ou s'il ne semble  avoir aucune limite ou que les deux methodes
94
 
!     on echou� (0). Avant le premier passage, elle vaut -1.
95
 
 
96
 
if (imetho.ne.0) then
97
 
 
98
 
!===============================================================================
99
 
! 1. AU PREMIER PASSAGE : INITIALISATIONS
100
 
!===============================================================================
101
 
 
102
 
  if (imetho.eq.-1) then
103
 
 
104
 
! ---     Premier passage : on essaie d'abord TREMAI
105
 
!           Si l'on obtient pas de temps CPU limite, on essaie
106
 
!           TCPUMX, qui se base sur la presence de la variable
107
 
!           d'environnement CS_MAXTIME.
108
 
 
109
 
    call tremai(trest0, itlim)
110
 
    !==========
111
 
    if (itlim.eq.1) then
112
 
      imetho = 1
113
 
    else
114
 
      call tcpumx(trest0, itlim)
115
 
      !==========
116
 
      if (itlim.eq.1) then
117
 
        imetho = 2
118
 
      endif
119
 
    endif
120
 
 
121
 
!         Si une des methodes fonctionne et indique une limite :
122
 
 
123
 
    if (imetho.ge.0) then
124
 
 
125
 
      ntcab0 = ntcabs
126
 
 
127
 
! ---       Temps restant et temps CPU a l'iteration courante
128
 
!           (qui sera ensuite la precedente)
129
 
 
130
 
      trestp = trest0
131
 
 
132
 
      call dmtmps(tcpupr)
133
 
      !==========
134
 
 
135
 
    endif
136
 
 
137
 
  else
138
 
 
139
 
!===============================================================================
140
 
! 2. TEMPS MOYEN PAR ITERATION
141
 
!===============================================================================
142
 
 
143
 
! --- Temps de l'iteration precedente
144
 
 
145
 
    call dmtmps(tcpuco)
146
 
    !==========
147
 
    titpre = tcpuco-tcpupr
148
 
 
149
 
 
150
 
! --- Temps restant courant (temps restant pour le process en cours,
151
 
!      le temps des autres processes, compilation etc. non compris)
152
 
! --- Temps moyen par iteration depuis le debut
153
 
 
154
 
    if (imetho.eq.1) then
155
 
      call tremai(trestc, itlim)
156
 
      !==========
157
 
      tmoy00 = (trest0-trestc)/dble(ntcabs-ntcab0)
158
 
    else if (imetho.eq.2) then
159
 
!           Ici on utilise le temps alloue initialement
160
 
      trestc = max(trest0 - tcpuco,0.d0)
161
 
      tmoy00 = tcpuco/dble(ntcabs-ntcab0)
162
 
    endif
163
 
 
164
 
! --- Estimation du temps par iteration
165
 
!       ALPHA -> 0 EST PLUS SUR
166
 
 
167
 
    alpha = 0.25d0
168
 
    tmoyit = alpha*titpre + (1.d0-alpha)*tmoy00
169
 
 
170
 
! --- Temps restant iteration courante (qui sera ensuite la precedente)
171
 
 
172
 
    trestp = trestc
173
 
 
174
 
! --- Temps CPU iteration courante (qui sera ensuite la precedente)
175
 
 
176
 
    tcpupr = tcpuco
177
 
 
178
 
!===============================================================================
179
 
! 3. TEMPS NECESSAIRE POUR UNE ITERATION DE PLUS
180
 
!===============================================================================
181
 
 
182
 
! --- Marge pour les sorties ...
183
 
!      100 fois une iteration ou 10% du temps alloue au process (-lt)
184
 
!        et au moins 50s ou 1% du temps alloue alloue au process (-lt)
185
 
 
186
 
!      Soit pour des jobs de
187
 
!        moins de    1000 iter     :  10% du temps alloue
188
 
!        plus  de    1000 iter et
189
 
!          moins de 10000 iter     : 100 fois une iter
190
 
!        plus  de   10000 iter     :   1% du temps alloue
191
 
 
192
 
 
193
 
    if (tmarus.lt.0.d0) then
194
 
 
195
 
      aa = 100.d0
196
 
      bb = 0.10d0
197
 
      cc = 0.01d0
198
 
      tmamin = 50.d0
199
 
 
200
 
      tmarge = min(tmoyit*aa,trest0*bb)
201
 
      tmarge = max(tmarge,tmamin)
202
 
      tmarge = max(tmarge,trest0*cc)
203
 
 
204
 
    else
205
 
 
206
 
      tmarge = tmarus
207
 
 
208
 
    endif
209
 
 
210
 
 
211
 
! --- Temps necessaire pour une iteration de plus
212
 
 
213
 
    titsup = tmoyit + tmarge
214
 
 
215
 
!===============================================================================
216
 
! 4. TEST (en parallele, le processeur 0 commande)
217
 
!===============================================================================
218
 
 
219
 
! On s'arrete si le temps restant minimum est inferieur au
220
 
!   temps maximum estime pour une iter de plus.
221
 
! Les notions de min et de max sont relatives aux calculs en parallele.
222
 
!   En effet, les temps sont estimes separement par les differents
223
 
!   processeurs et il faut qu'ils aient tous le temps de finir.
224
 
!   Avec cette methode la marge est la meme pour tous.
225
 
! Bien noter que UN SEUL processeur doit decider d'arreter le calcul.
226
 
 
227
 
    tresmn = trestc
228
 
    titsmx = titsup
229
 
    if(irangp.ge.0) then
230
 
      call parmin(tresmn)
231
 
      call parmax(titsmx)
232
 
          endif
233
 
    if(irangp.lt.0.or.irangp.eq.0) then
234
 
      if (tresmn.lt.titsmx) then
235
 
        ntmabs = ntcabs
236
 
        write(nfecra,1000) ntmabs
237
 
      endif
238
 
    else
239
 
      ntmabs = 0
240
 
    endif
241
 
! Broadcast
242
 
    if(irangp.ge.0) then
243
 
      irangs  = 0
244
 
      lng     = 1
245
 
      itmp(1) = ntmabs
246
 
      call parbci(irangs,lng,itmp)
247
 
      ntmabs = itmp(1)
248
 
    endif
249
 
 
250
 
    if (ntcabs.eq.ntmabs) then
251
 
      write(nfecra,1100) trestc, titsup, tmoy00, titpre, tmarge
252
 
    endif
253
 
 
254
 
  endif
255
 
 
256
 
endif
257
 
 
258
 
 
259
 
!===============================================================================
260
 
! 5. FORMATS
261
 
!===============================================================================
262
 
 
263
 
#if defined(_CS_LANG_FR)
264
 
 
265
 
 1000 format(/,                                                   &
266
 
'===============================================================',&
267
 
/,'   ** ARRET PAR MANQUE DE TEMPS ',                             &
268
 
/,'      ------------------------- ',                             &
269
 
/,'      NOMBRE DE PAS DE TEMPS MAX IMPOSE A NTCABS : ',I10,    /,&
270
 
'===============================================================',&
271
 
                                                                /)
272
 
 
273
 
 1100 format(/,                                                   &
274
 
'===============================================================',&
275
 
/,'   ** GESTION DU TEMPS RESTANT ',                              &
276
 
/,'      ------------------------ ',                              &
277
 
/,'      TEMPS RESTANT ALLOUE AU PROCESS          : ',E14.5,      &
278
 
/,'      TEMPS ESTIME POUR UNE ITERATION DE PLUS  : ',E14.5,      &
279
 
/,'        DUREE MOYENNE D''UNE ITERATION EN TEMPS : ',E14.5,     &
280
 
/,'        DUREE DE L''ITERATION PRECEDENTE        : ',E14.5,     &
281
 
/,'        MARGE DE SECURITE                      : ',E14.5,   /, &
282
 
'===============================================================',&
283
 
                                                                /)
284
 
 
285
 
#else
286
 
 
287
 
 1000 format(/,                                                   &
288
 
'===============================================================',&
289
 
/,'   ** STOP BECAUSE OF TIME EXCEEDED'                           &
290
 
/,'      -----------------------------',                          &
291
 
/,'      MAX NUMBER OF TIME STEP SET TO NTCABS: ',I10,          /,&
292
 
'===============================================================',&
293
 
                                                                /)
294
 
 
295
 
 1100 format(/,                                                   &
296
 
'===============================================================',&
297
 
/,'   ** REMAINING TIME MANAGEMENT ',                             &
298
 
/,'      ------------------------- ',                             &
299
 
/,'      REMAINING TIME ALLOCATED TO THE PROCESS   : ',E14.5,     &
300
 
/,'      ESTIMATED TIME FOR ANOTHER TIME STEP      : ',E14.5,     &
301
 
/,'        MEAN TIME FOR A TIME STEP               : ',E14.5,     &
302
 
/,'        TIME FOR THE PREVIOUS TIME STEP         : ',E14.5,     &
303
 
/,'        SECURITY MARGIN                         : ',E14.5,   /,&
304
 
'===============================================================',&
305
 
                                                                /)
306
 
 
307
 
#endif
308
 
 
309
 
end subroutine