4 SUBROUTINE conf_gcm( tapedef, etatinit )
29 LOGICAL,
INTENT(IN) :: etatinit
30 INTEGER,
INTENT(IN) :: tapedef
34 include
"dimensions.h"
38 include
"comdissnew.h"
46 CHARACTER ch1*72,ch2*72,ch3*72,ch4*12
47 REAL clonn,clatt,grossismxx,grossismyy
48 REAL dzoomxx,dzoomyy, tauxx,tauyy
49 LOGICAL fxyhypbb, ysinuss
51 character(len=*),
parameter :: modname=
"conf_gcm"
52 character (len=80) :: abort_message
54 integer,
external :: OMP_GET_NUM_THREADS
93 OPEN(
unit=
lunout,file=
'lmdz.out_0000',action=
'write', &
94 status=
'unknown',form=
'formatted')
103 if ((omp_get_num_threads()>1).and.
adjust)
then
104 write(
lunout,*)
'conf_gcm: Error, adjust should be set to n' &
105 ,
' when running with OpenMP threads'
106 abort_message =
'Wrong value for adjust'
139 calend =
'earth_360d'
140 CALL getin(
'calend', calend)
265 CALL getin(
'lstardis',lstardis)
325 CALL getin(
'dissip_zref',dissip_zref )
340 CALL getin(
'mode_top_bound',mode_top_bound)
369 "adjust does not work with ok_guide", 1)
408 test_etatinit:
IF (.not. etatinit)
then
415 CALL getin(
'clon',clonn)
423 CALL getin(
'clat',clatt)
425 IF( abs(
clat - clatt).GE. 0.001 )
THEN
426 write(
lunout,*)
'conf_gcm: La valeur de clat passee par run.def', &
427 ' est differente de celle lue sur le fichier start '
437 CALL getin(
'grossismx',grossismxx)
439 IF( abs(
grossismx - grossismxx).GE. 0.001 )
THEN
440 write(
lunout,*)
'conf_gcm: La valeur de grossismx passee par ', &
441 'run.def est differente de celle lue sur le fichier start '
451 CALL getin(
'grossismy',grossismyy)
453 IF( abs(
grossismy - grossismyy).GE. 0.001 )
THEN
454 write(
lunout,*)
'conf_gcm: La valeur de grossismy passee par ', &
455 'run.def est differente de celle lue sur le fichier start '
461 'conf_gcm: *** ATTENTION !! grossismx < 1 . *** '
469 'conf_gcm: *** ATTENTION !! grossismy < 1 . *** '
485 CALL getin(
'fxyhypb',fxyhypbb)
489 write(
lunout,*)
' ******** PBS DANS CONF_GCM ******** '
490 write(
lunout,*)
' *** fxyhypb lu sur le fichier start est ', &
491 'F alors qu il est T sur run.def ***'
495 IF( .NOT.fxyhypbb )
THEN
496 write(
lunout,*)
' ******** PBS DANS CONF_GCM ******** '
497 write(
lunout,*)
' *** fxyhypb lu sur le fichier start est ', &
498 'T alors qu il est F sur run.def **** '
509 CALL getin(
'dzoomx',dzoomxx)
512 IF( abs(
dzoomx - dzoomxx).GE. 0.001 )
THEN
513 write(
lunout,*)
'conf_gcm: La valeur de dzoomx passee par ', &
514 'run.def est differente de celle lue sur le fichier start '
525 CALL getin(
'dzoomy',dzoomyy)
528 IF( abs(
dzoomy - dzoomyy).GE. 0.001 )
THEN
529 write(
lunout,*)
'conf_gcm: La valeur de dzoomy passee par ', &
530 'run.def est differente de celle lue sur le fichier start '
540 CALL getin(
'taux',tauxx)
543 IF( abs(
taux - tauxx).GE. 0.001 )
THEN
544 write(
lunout,*)
'conf_gcm: La valeur de taux passee par ', &
545 'run.def est differente de celle lue sur le fichier start '
555 CALL getin(
'tauy',tauyy)
558 IF( abs(tauy - tauyy).GE. 0.001 )
THEN
559 write(
lunout,*)
'conf_gcm: La valeur de tauy passee par ', &
560 'run.def est differente de celle lue sur le fichier start '
575 CALL getin(
'ysinus',ysinuss)
577 IF( .NOT.ysinus )
THEN
579 write(
lunout,*)
' ******** PBS DANS CONF_GCM ******** '
580 write(
lunout,*)
' *** ysinus lu sur le fichier start est F', &
581 ' alors qu il est T sur run.def ***'
585 IF( .NOT.ysinuss )
THEN
586 write(
lunout,*)
' ******** PBS DANS CONF_GCM ******** '
587 write(
lunout,*)
' *** ysinus lu sur le fichier start est T', &
588 ' alors qu il est F sur run.def **** '
603 'WARNING : option offline does not work with adjust=y :'
604 WRITE(
lunout,*)
'the files defstoke.nc, fluxstoke.nc ', &
605 'and fluxstokev.nc will not be created'
607 'only the file phystoke.nc will still be created '
654 write(
lunout,*)
' #########################################'
655 write(
lunout,*)
' Configuration des parametres du gcm: '
657 write(
lunout,*)
' calend = ', calend
669 write(
lunout,*)
' lstardis = ', lstardis
681 write(
lunout,*)
' clonn = ', clonn
682 write(
lunout,*)
' clatt = ', clatt
685 write(
lunout,*)
' fxyhypbb = ', fxyhypbb
686 write(
lunout,*)
' dzoomxx = ', dzoomxx
687 write(
lunout,*)
' dzoomy = ', dzoomyy
688 write(
lunout,*)
' tauxx = ', tauxx
689 write(
lunout,*)
' tauyy = ', tauyy
731 'conf_gcm: *** ATTENTION !! grossismx < 1 . *** '
738 write(
lunout,*)
'conf_gcm: ***ATTENTION !! grossismy < 1 . *** '
784 CALL getin(
'tauy',tauy)
793 CALL getin(
'ysinus',ysinus)
804 'WARNING : option offline does not work with adjust=y :'
805 WRITE(
lunout,*)
'the files defstoke.nc, fluxstoke.nc ', &
806 'and fluxstokev.nc will not be created'
808 'only the file phystoke.nc will still be created '
864 write(
lunout,*)
'WARNING !!! '
865 write(
lunout,*)
"Le zoom en longitude est incompatible", &
866 " avec l'utilisation du filtre FFT ", &
867 "---> FFT filter not active"
890 CALL getin(
'vert_prof_dissip', vert_prof_dissip)
891 call assert(vert_prof_dissip == 0 .or. vert_prof_dissip == 1, &
892 "bad value for vert_prof_dissip")
899 ok_gradsfile = .
false.
900 CALL getin(
'ok_gradsfile',ok_gradsfile)
918 write(
lunout,*)
' #########################################'
919 write(
lunout,*)
' Configuration des parametres de cel0' &
922 write(
lunout,*)
' calend = ', calend
933 write(
lunout,*)
' lstardis = ', lstardis
953 write(
lunout,*)
' tauy = ', tauy
963 write(
lunout,*)
' ok_gradsfile = ', ok_gradsfile
!$Header!c!c!c include serre h!c REAL dzoomy
!$Header!c!c!c include serre h!c REAL alphax
integer, save iapp_tracvl
!$Id mode_top_bound COMMON comconstr omeg dissip_factz
character(len=4), save config_inca
!$Header!c!c!c include serre h!c REAL && grossismx
logical, save use_filtre_fft
!$Header!c!c!c include serre h!c REAL clon
!$Id ysinus ok_gradsfile ok_limit
character(len=10), save planet_type
subroutine abort_gcm(modname, message, ierr)
!$Id Turb_fcg_gcssold get_uvd hqturb_gcssold endif!large scale llm day day1 day day1 *dt_toga endif!time annee_ref dt_toga u_toga vq_toga w_prof vq_prof llm day day1 day day1 *dt_dice endif!time annee_ref dt_dice swup_dice vg_dice omega_dice tg_prof vg_profd w_profd omega_profd!do llm!print llm l llm
!$Id ysinus ok_gradsfile hybrid COMMON logici iflag_phys
!$Id mode_top_bound COMMON comconstr omeg dissip_zref tau_top_bound
logical, save output_grads_dyn
logical, save use_mpi_alloc
!$Id itapm1 ENDIF!IM on interpole les champs sur les niveaux STD de pression!IM a chaque pas de temps de la physique c!positionnement de l argument logique a false c!pour ne pas recalculer deux fois la meme chose!c!a cet effet un appel a plevel_new a ete deplace c!a la fin de la serie d appels c!la boucle DO nlevSTD a ete internalisee c!dans d ou la creation de cette routine c c!CALL false
!$Id ysinus ok_gradsfile ok_etat0
integer, save dissip_period
!FH On elimine toutes les clefs physiques dans la dynamique prt_level
subroutine conf_gcm(tapedef, etatinit)
!$Id itapm1 ENDIF!IM on interpole les champs sur les niveaux STD de pression!IM a chaque pas de temps de la physique c!positionnement de l argument logique a false c!pour ne pas recalculer deux fois la meme chose!c!a cet effet un appel a plevel_new a ete deplace c!a la fin de la serie d appels c!la boucle DO nlevSTD a ete internalisee c!dans d ou la creation de cette routine c c!CALL ulevSTD CALL &zphi philevSTD CALL &zx_rh rhlevSTD!DO klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon du jour ou toutes les read_climoz CALL true
character(len=4), save type_trac
!$Id ysinus ok_gradsfile hybrid COMMON logici iflag_trac LOGICAL purmats
!$Header!c!c!c include serre h!c REAL dzoomx
!$Id mode_top_bound COMMON comconstr omeg dissip_deltaz
!$Header!c!c!c include serre h!c REAL grossismy
!$Header!c!c!c include serre h!c REAL taux
integer, save nsplit_phys
!$Header!INCLUDE comdissip h COMMON comdissip tetatemp
integer, save ip_ebil_dyn
!$Header!c!c!c include serre h!c REAL clat
!$Header!c!c!c include serre h!c REAL alphay
!$Header!integer nvarmx s s unit
!$Header!gestion des impressions de sorties et de débogage la sortie standard prt_level COMMON comprint lunout
!$Header!INCLUDE comdissip h COMMON comdissip coefdis