5 &(motcar,file_desc,path,ncar,code,cas_file,dico_file)
83 INTEGER,
INTENT(IN) :: NCAR
84 CHARACTER(LEN=24),
INTENT(IN) :: CODE
85 CHARACTER(LEN=PATH_LEN),
INTENT(IN) :: PATH
86 CHARACTER(LEN=PATH_LEN),
INTENT(INOUT) :: MOTCAR(
maxkeyword)
87 CHARACTER(LEN=PATH_LEN),
INTENT(INOUT) :: FILE_DESC(4,
maxkeyword)
89 CHARACTER(LEN=PATH_LEN),
INTENT(IN) :: CAS_FILE
90 CHARACTER(LEN=PATH_LEN),
INTENT(IN) :: DICO_FILE
99 DOUBLE PRECISION :: SUMAVAI
101 LOGICAL :: DOC,EFFPEN
103 CHARACTER(LEN=PATH_LEN) :: NOM_CAS
104 CHARACTER(LEN=PATH_LEN) :: NOM_DIC
107 CHARACTER(LEN=PATH_LEN) TEMPVAR
108 INTEGER :: ID_DICO, ID_CAS
112 CHARACTER(LEN=2) CHAR2
138 nom_dic=path(1:ncar)//
'SISDICO' 139 nom_cas=path(1:ncar)//
'SISCAS' 147 IF((cas_file(1:1).NE.
' ').AND.(dico_file(1:1).NE.
' '))
THEN 148 WRITE(
lu,*)
'FIXED DICO AND STEERING FILE PRESENT' 151 WRITE(
lu,*)
'NOM_DIC',nom_dic
152 WRITE(
lu,*)
'NOM_CAS',nom_cas
155 CALL get_free_id(id_dico)
156 OPEN(id_dico,file=nom_dic,form=
'FORMATTED',action=
'READ')
157 CALL get_free_id(id_cas)
158 OPEN(id_cas,file=nom_cas,form=
'FORMATTED',action=
'READ')
165 & motint, motrea ,motlog , motcar ,
166 & motcle, trouve ,id_dico, id_cas,.false. ,file_desc)
185 IF(
sis_files(i)%TELNAME.EQ.
'SISHYD')
THEN 187 ELSEIF(
sis_files(i)%TELNAME.EQ.
'SISGEO')
THEN 189 ELSEIF(
sis_files(i)%TELNAME.EQ.
'SISCLI')
THEN 191 ELSEIF(
sis_files(i)%TELNAME.EQ.
'SISPRE')
THEN 193 ELSEIF(
sis_files(i)%TELNAME.EQ.
'SISRES')
THEN 195 ELSEIF(
sis_files(i)%TELNAME.EQ.
'SISREF')
THEN 197 ELSEIF(
sis_files(i)%TELNAME.EQ.
'SISCOU')
THEN 199 ELSEIF(
sis_files(i)%TELNAME.EQ.
'SISFON')
THEN 201 ELSEIF(
sis_files(i)%TELNAME.EQ.
'SISSEC')
THEN 203 ELSEIF(
sis_files(i)%TELNAME.EQ.
'SISSEO')
THEN 205 ELSEIF(
sis_files(i)%TELNAME.EQ.
'SISLIQ')
THEN 207 ELSEIF(
sis_files(i)%TELNAME.EQ.
'SISFLX')
THEN 210 ELSEIF(
sis_files(i)%TELNAME.EQ.
'SINACT')
THEN 212 ELSEIF(
sis_files(i)%TELNAME.EQ.
'SINPOL')
THEN 214 ELSEIF(
sis_files(i)%TELNAME.EQ.
'SINREF')
THEN 216 ELSEIF(
sis_files(i)%TELNAME.EQ.
'SINRST')
THEN 219 ELSEIF(
sis_files(i)%TELNAME.EQ.
'VSPRES')
THEN 232 maxfro = motint( adress(1,58) )
271 icf = motint( adress(1, 2) )
272 npas = motint( adress(1, 3) )
273 nmaree = motint( adress(1, 4) )
276 leopr = motint( adress(1, 6) )
277 lispr = motint( adress(1, 7) )
278 optban = motint( adress(1, 11) )
279 lvmac = motint( adress(1, 12) )
280 nsous = motint( adress(1, 14) )
282 mardat(1) = motint( adress(1, 15) )
283 mardat(2) = motint( adress(1, 15) + 1 )
284 mardat(3) = motint( adress(1, 15) + 2 )
285 martim(1) = motint( adress(1, 16) )
286 martim(2) = motint( adress(1, 16) + 1 )
287 martim(3) = motint( adress(1, 16) + 2 )
289 slvsed%SLV = motint( adress(1, 17) )
290 slvsed%KRYLOV = motint( adress(1, 18) )
291 slvsed%PRECON = motint( adress(1, 19) )
292 slvsed%NITMAX = motint( adress(1, 20) )
293 choix = motint( adress(1, 21) )
294 dirflu = motint( adress(1, 22) )
295 npriv = motint( adress(1, 23) )
296 nadvar = motint( adress(1,30) )
304 IF(ncsize.NE.motint(adress(1,24)))
THEN 305 WRITE(
lu,*)
'DIFFERENT NUMBER OF PARALLEL PROCESSORS:' 306 WRITE(
lu,*)
'DECLARED BEFORE (CASE OF COUPLING ?):',ncsize
307 WRITE(
lu,*)
'SISYPHE :',motint(adress(1,24))
308 WRITE(
lu,*)
'VALUE ',ncsize,
' IS KEPT' 310 resol = motint( adress(1, 25) )
311 slvtra%SLV = motint( adress(1, 26) )
312 slvtra%KRYLOV = motint( adress(1, 27) )
313 slvtra%PRECON = motint( adress(1, 28) )
314 slvtra%NITMAX = motint( adress(1, 29) )
315 optdif = motint( adress(1, 31) )
316 optsup = motint( adress(1, 32) )
317 produc = motint( adress(1, 33) )
318 optass = motint( adress(1, 34) )
319 opdtra = motint( adress(1, 35) )
320 kfrot = motint( adress(1, 37) )
321 ncondis = motint( adress(1, 38) )
322 slopeff = motint( adress(1, 39) )
323 devia = motint( adress(1, 40) )
324 nomblay = motint( adress(1,251) )
325 nsicla = motint( adress(1,252) )
326 hidfac = motint( adress(1,253) )
327 icq = motint( adress(1, 41) )
331 CALL check_allocate(err,
'CTRLSC')
334 ctrlsc(k) = motint( adress(1,42) + k-1 )
338 i_orig = motint( adress(1,43) )
339 j_orig = motint( adress(1,43)+1 )
340 debug = motint( adress(1,44) )
342 icr = motint(adress(1,46) )
344 iks = motint(adress(1,47) )
349 vsmtype = motint(adress(1,53) )
353 maxadv = motint(adress(1,54))
361 ELSEIF(
resol.EQ.2)
THEN 364 ELSEIF(
resol.EQ.5)
THEN 369 IF(trouve(1,55).EQ.2)
THEN 370 optadv = motint(adress(1,55))
383 rc = motrea( adress(2, 1) )
384 xmve = motrea( adress(2, 2) )
385 xmvs = motrea( adress(2, 3) )
387 fdm(k) = motrea( adress(2, 4) + k-1 )
390 IF(trouve(2,28).EQ.2)
THEN 392 fdm(k) = motrea( adress(2,28) + k-1 )
395 xkv = motrea( adress(2, 5) )
398 ac(k) = motrea( adress(2, 6) + k-1 )
404 IF(dimens(2,6).LT.
nsicla)
THEN 406 ac(k) = motrea( adress(2, 6)+max(dimens(2,6),1)-1 )
409 sfon = motrea( adress(2, 7) )
410 grav = motrea( adress(2, 8) )
411 zero = motrea( adress(2, 9) )
413 vce = motrea( adress(2, 10) )
414 hmin = motrea( adress(2, 11) )
415 delt = motrea( adress(2, 12) )
416 tprec = motrea( adress(2, 13) )
417 pmaree = motrea( adress(2, 14) )
418 teta = motrea( adress(2, 15) )
419 beta = motrea( adress(2, 16) )
420 slvsed%EPS = motrea( adress(2, 17) )
422 xkx = motrea( adress(2, 19) )
423 xky = motrea( adress(2, 20) )
424 slvtra%EPS = motrea( adress(2, 21) )
427 xwc(k) = motrea( adress(2, 22) + k-1 )
429 IF(dimens(2,22).LT.
nsicla)
THEN 430 DO k=dimens(2,22)+1,
nsicla 431 xwc(k) = motrea( adress(2, 22)+dimens(2,22)-1 )
436 phised = motrea( adress(2, 25) )
437 beta2 = motrea( adress(2, 26) )
438 bijk = motrea( adress(2, 27) )
448 cs0(k)=motrea( adress(2,30) + k-1 )
453 IF(dimens(2,31).GT.0)
THEN 477 IF(dimens(2,32).GT.0)
THEN 479 conc_vase(k)=motrea( adress(2,32) + k-1 )
487 IF(dimens(2,34).GT.0)
THEN 489 toce_vase(k)=motrea( adress(2,34) + k-1 )
498 vitcd= motrea( adress(2,36))
504 tass = motlog(adress(3,23))
505 itass = motint(adress(1,48) )
523 IF(dimens(2,33).GT.0)
THEN 534 coef_n= motrea( adress(2,39))
542 soldis(k)=motrea(adress(2,51)+k-1)
553 hidi(k) = motrea( adress(2,253) + k-1 )
554 IF (trouve(2,255).EQ.1)
THEN 557 fd90(k)= motrea( adress(2,255) + k-1 )
559 ava0(k) = motrea( adress(2,258) + k-1 )
561 elay0 = motrea( adress(2,259) )
564 mpm = motrea( adress(2,260) )
566 alpha = motrea( adress(2,261) )
568 mofac = motrea( adress(2,262) )
586 IF (trouve(2, 22).EQ.2)
calwc = .true.
593 IF (trouve(2, 6).EQ.2)
calac = .true.
596 bilma = motlog( adress(3, 1) )
597 perma = motlog( adress(3, 2) )
598 bandec = motlog( adress(3, 3) )
599 valid = motlog( adress(3, 4) )
601 lumpi = motlog( adress(3, 6) )
602 susp = motlog( adress(3, 7) )
603 charr = motlog( adress(3, 8) )
604 houle = motlog( adress(3, 10) )
606 lcondis = motlog( adress(3, 12) )
607 lgrafed = motlog( adress(3, 13) )
609 debu = motlog( adress(3, 14) )
613 IF(code(1:9).EQ.
'TELEMAC3D')
seccurrent = .false.
614 unit = motlog( adress(3, 17) )
615 vf = motlog( adress(3,253) )
620 IF(dimens(3,19).GT.0)
THEN 622 sedco(k) = motlog( adress(3,19) + k-1 )
625 slide = motlog( adress(3, 20) )
626 dift = motlog( adress(3, 21) )
627 effpen = motlog( adress(3, 22) )
633 mixte=motlog(adress(3,24))
635 nestor=motlog(adress(3,25))
637 kspred =motlog(adress(3,26))
643 set_lag = motlog(adress(3,27) )
649 doflux = motlog(adress(3,61) )
650 IF ( code(1:7) .NE.
'TELEMAC' )
THEN 666 titca = motcar( adress(4, 1) )(1:72)
667 sortis = motcar( adress(4, 2) )(1:72)
668 varim = motcar( adress(4, 3) )(1:72)
671 WRITE(
lu,*)
'THE FOLLOWING KEYWORD IS MANDATORY:' 672 WRITE(
lu,*)
'GEOMETRY FILE (FICHIER DE GEOMETRIE)' 678 WRITE(
lu,*)
'THE FOLLOWING KEYWORD IS MANDATORY:' 679 WRITE(
lu,*)
'BOUNDARY CONDITIONS FILE '//
680 &
'(FICHIER DES CONDITIONS AUX LIMITES)' 690 WRITE(
lu,*)
'THE FOLLOWING KEYWORD IS MANDATORY:' 691 WRITE(
lu,*)
'RESULTS FILE (FICHIER DES RESULTATS)' 745 WRITE(char2,
'(I2)') i
746 names_advar(i) =
'DERIVATIVE '//adjustl(char2)//
' ' 757 tempvar = motcar(adress(4,51) )
767 102
FORMAT(1
x,/,19
x,
'********************************************',/,
768 & 19
x,
'* LECDON: *',/,
769 & 19
x,
'* AFTER CALLING DAMOCLES *',/,
770 & 19
x,
'* CHECKING OF DATA READ *',/,
771 & 19
x,
'* IN THE STEERING FILE *',/,
772 & 19
x,
'********************************************',/)
790 IF ((
npriv.LT.i).AND.
824 IF(
teta.LT.0.d0.OR.
teta.GT.1.d0)
THEN 826 51
FORMAT(/,1
x,
'BAD VALUE FOR TETA ! ',/
827 & ,1
x,
'TETA MUST BE WITHIN 0 AND 1 ')
848 71
FORMAT(/,1
x,
'VALIDATION IS NOT POSSIBLE : ',/
849 & ,1
x,
'NO REFERENCE FILE ! ')
859 81
FORMAT(/,1
x,
'THE MAXIMUM NUMBER OF SEDIMENT CLASSES IS', i2)
866 sumavai = sumavai +
ava0(i)
868 IF(abs(sumavai-1).GE.1.d-8)
THEN 871 91
FORMAT(/,1
x,
'SUM OF SEDIMENT FRACTIONS IS NOT 1 ')
881 201
FORMAT(/,1
x,
'FINITE VOLUMES CHOSEN: ',/
882 & ,1
x,
'METHOD 4 FOR RIGID BED WILL BE USED ')
885 IF (
choix.EQ.4.AND..NOT.
vf)
THEN 888 301
FORMAT(/,1
x,
'FINITE ELEMENTS CHOSEN: ',/
889 & ,1
x,
'METHOD 4 FOR RIGID BED CAN NOT BE USED, METHOD 3 US 902 111
FORMAT(/,1
x,
'CHOICE OF TRANSPORT FORMULA AND HIDING FACTOR FORMU 903 &LATION NOT ALLOWED ')
910 IF(code(1:7).EQ.
'TELEMAC'.AND.
914 113
FORMAT(/,1
x,
'COUPLING: HYDRODYNAMIC FILE IGNORED')
922 313
FORMAT(/,1
x,
'COMPUTATION CONTINUED:',/,
923 & 1
x,
'PREVIOUS SEDIMENTOLOGICAL FILE MISSING')
931 213
FORMAT(/,1
x,
'NO COMPUTATION CONTINUED:',/,
932 & 1
x,
'PREVIOUS SEDIMENTOLOGICAL FILE IGNORED')
945 303
FORMAT(1
x,
'RESOLVING METHOD NOT IMPLEMENTED : ',1i6)
953 IF(
icf.NE.4.AND.
icf.NE.5.AND.
icf.NE.8.AND.
icf.NE.9)
THEN 955 1304
FORMAT(
' TRANSPORT FORMULA',1i3,1
x,
956 &
'DOES NOT TAKE WAVES INTO ACCOUNT,',/,1
x,
957 &
'TRY 4, 5, 8 OR 9')
971 1302
FORMAT(
'FOR THE FORMULA',1i3,/,1
x,
972 &
'THE SUSPENSION TERM IS CALCULATED TWICE,' 973 & ,
' WITH TOTAL LOAD FORMULA AND SUSPENSION ')
981 1402
FORMAT(
'FOR THE BIJKER REFERENCE CONCENTRATION',1i3,/,1
x,
982 &
'BEDLOAD MUST BE COMPUTED, CHOOSE:',/,1
x,
995 1404
FORMAT(
'BED-LOAD TRANSPORT FORMULA, HERE ICF=',1i3,/,1
x,
996 &
'MUST HAVE A THRESHOLD',/,1
x,
997 &
'IF FORMULA FOR SLOPE EFFECT=2 (SOULSBY)')
1031 WRITE (
lu,*)
'NUMBER OF BED LOAD MODEL LAYERS LARGER THAN ' 1032 WRITE (
lu,*)
'THE MAXIMUM PROGRAMMED VALUE OF ',
nlaymax
double precision, dimension(:), allocatable, target cbor_classe
integer, parameter adv_nsc_tf
subroutine nomvar_sisyphe(TEXTE, TEXTPR, MNEMO, NSICLA, UNITE, MAXVAR, NPRIV, NOMBLAY, N_NAMES_PRIV, NAMES_PRIVE, NADVAR, NAMES_ADVAR)
double precision, target phised
integer, parameter adv_psi
character(len=3) bingeosis
integer, parameter maxvar
character(len=3) binrefsis
integer, parameter adv_lpo
double precision, dimension(nsiclm) hidi
logical, dimension(maxvar) sorleo
integer, parameter adv_sup
double precision hmin_bedload
double precision, dimension(nsiclm) ava0
double precision, target xkv
subroutine lecdon_sisyphe(MOTCAR, FILE_DESC, PATH, NCAR, CODE, CAS_FILE, DICO_FILE)
subroutine lecdon_split_outputpoints(INT_LIST, POINT_ARRAY, FULLOUTPUT)
logical, dimension(:), allocatable okcgl
subroutine read_submit(FILES, NFILES, SUBMIT, NMOT)
double precision, dimension(nsiclm), target xwc
integer, dimension(3) mardat
double precision, target tprec
integer, dimension(100) cvsmoutput
character(len=3) binhydsis
integer, parameter maxkeyword
character(len=32), dimension(4) names_prive
integer, parameter nsiclm
double precision conc_max
integer, parameter adv_nsc
double precision conc_gel
character(len=3) binressis
double precision, target partheniades
integer, dimension(:), allocatable ctrlsc
double precision, dimension(nlaymax) trans_mass
double precision, target delt
double precision, dimension(nsiclm) fd90
integer, parameter maxlu_sis
logical, dimension(maxvar) sorimp
double precision, dimension(:), pointer x
integer, parameter adv_psi_tf
double precision, dimension(nsiclm), target fdm
logical, dimension(nsiclm) sedco
subroutine sortie(CHAINE, MNEMO, NBRE, SORLEO)
double precision, dimension(:), allocatable soldis
integer, parameter adv_lpo_tf
logical, dimension(:), allocatable okqgl
subroutine damocle(ADRESS, DIMENS, NMAX, DOC, LLNG, LLU, MOTINT, MOTREA, MOTLOG, MOTCAR, MOTCLE, TROUVE, NFICMO, NFICDA, GESTD, MOTATT)
character(len=32), dimension(maxvar) names_advar
logical ad_linsolv_resetderiv
double precision, dimension(nlaymax) toce_vase
double precision, dimension(nlaymax) conc_vase
integer, parameter adv_car
character(len=8), dimension(maxvar) mnemo
double precision, target kspratio
double precision, target alpha
character(len=32), dimension(maxvar) textpr
integer, parameter nlaymax
double precision teta_susp
double precision, dimension(nsiclm) cs0
integer, dimension(3) martim
character(len=3) binpresis
logical ad_linsolv_derivative_convergence
double precision crit_cfd
character(len=32), dimension(maxvar) texte
double precision, target beta2
double precision, dimension(nsiclm), target ac
double precision, target mpm
double precision, target csf_sable
type(bief_file), dimension(maxlu_sis), target sis_files