4 SUBROUTINE conf_gcm( tapedef, etatinit )
30 LOGICAL,
INTENT(IN) :: etatinit
31 INTEGER,
INTENT(IN) :: tapedef
35 include
"dimensions.h"
39 include
"comdissnew.h"
47 CHARACTER ch1*72,ch2*72,ch3*72,ch4*12
48 REAL clonn,clatt,grossismxx,grossismyy
49 REAL dzoomxx,dzoomyy, tauxx,tauyy
50 LOGICAL fxyhypbb, ysinuss
52 character(len=*),
parameter :: modname=
"conf_gcm"
53 character (len=80) :: abort_message
55 integer,
external :: OMP_GET_NUM_THREADS
94 OPEN(
unit=
lunout,file=
'lmdz.out_0000',action=
'write', &
95 status=
'unknown',form=
'formatted')
104 if ((omp_get_num_threads()>1).and.
adjust)
then
105 write(
lunout,*)
'conf_gcm: Error, adjust should be set to n' &
106 ,
' when running with OpenMP threads'
107 abort_message =
'Wrong value for adjust'
140 calend =
'earth_360d'
141 CALL getin(
'calend', calend)
266 CALL getin(
'lstardis',lstardis)
326 CALL getin(
'dissip_zref',dissip_zref )
341 CALL getin(
'mode_top_bound',mode_top_bound)
370 "adjust does not work with ok_guide", 1)
409 test_etatinit:
IF (.not. etatinit)
then
416 CALL getin(
'clon',clonn)
424 CALL getin(
'clat',clatt)
426 IF( abs(
clat - clatt).GE. 0.001 )
THEN
427 write(
lunout,*)
'conf_gcm: La valeur de clat passee par run.def', &
428 ' est differente de celle lue sur le fichier start '
438 CALL getin(
'grossismx',grossismxx)
440 IF( abs(
grossismx - grossismxx).GE. 0.001 )
THEN
441 write(
lunout,*)
'conf_gcm: La valeur de grossismx passee par ', &
442 'run.def est differente de celle lue sur le fichier start '
452 CALL getin(
'grossismy',grossismyy)
454 IF( abs(
grossismy - grossismyy).GE. 0.001 )
THEN
455 write(
lunout,*)
'conf_gcm: La valeur de grossismy passee par ', &
456 'run.def est differente de celle lue sur le fichier start '
462 'conf_gcm: *** ATTENTION !! grossismx < 1 . *** '
470 'conf_gcm: *** ATTENTION !! grossismy < 1 . *** '
486 CALL getin(
'fxyhypb',fxyhypbb)
490 write(
lunout,*)
' ******** PBS DANS CONF_GCM ******** '
491 write(
lunout,*)
' *** fxyhypb lu sur le fichier start est ', &
492 'F alors qu il est T sur run.def ***'
496 IF( .NOT.fxyhypbb )
THEN
497 write(
lunout,*)
' ******** PBS DANS CONF_GCM ******** '
498 write(
lunout,*)
' *** fxyhypb lu sur le fichier start est ', &
499 'T alors qu il est F sur run.def **** '
510 CALL getin(
'dzoomx',dzoomxx)
513 IF( abs(
dzoomx - dzoomxx).GE. 0.001 )
THEN
514 write(
lunout,*)
'conf_gcm: La valeur de dzoomx passee par ', &
515 'run.def est differente de celle lue sur le fichier start '
526 CALL getin(
'dzoomy',dzoomyy)
529 IF( abs(
dzoomy - dzoomyy).GE. 0.001 )
THEN
530 write(
lunout,*)
'conf_gcm: La valeur de dzoomy passee par ', &
531 'run.def est differente de celle lue sur le fichier start '
541 CALL getin(
'taux',tauxx)
544 IF( abs(
taux - tauxx).GE. 0.001 )
THEN
545 write(
lunout,*)
'conf_gcm: La valeur de taux passee par ', &
546 'run.def est differente de celle lue sur le fichier start '
556 CALL getin(
'tauy',tauyy)
559 IF( abs(tauy - tauyy).GE. 0.001 )
THEN
560 write(
lunout,*)
'conf_gcm: La valeur de tauy passee par ', &
561 'run.def est differente de celle lue sur le fichier start '
576 CALL getin(
'ysinus',ysinuss)
578 IF( .NOT.ysinus )
THEN
580 write(
lunout,*)
' ******** PBS DANS CONF_GCM ******** '
581 write(
lunout,*)
' *** ysinus lu sur le fichier start est F', &
582 ' alors qu il est T sur run.def ***'
586 IF( .NOT.ysinuss )
THEN
587 write(
lunout,*)
' ******** PBS DANS CONF_GCM ******** '
588 write(
lunout,*)
' *** ysinus lu sur le fichier start est T', &
589 ' alors qu il est F sur run.def **** '
604 'WARNING : option offline does not work with adjust=y :'
605 WRITE(
lunout,*)
'the files defstoke.nc, fluxstoke.nc ', &
606 'and fluxstokev.nc will not be created'
608 'only the file phystoke.nc will still be created '
655 write(
lunout,*)
' #########################################'
656 write(
lunout,*)
' Configuration des parametres du gcm: '
658 write(
lunout,*)
' calend = ', calend
670 write(
lunout,*)
' lstardis = ', lstardis
682 write(
lunout,*)
' clonn = ', clonn
683 write(
lunout,*)
' clatt = ', clatt
686 write(
lunout,*)
' fxyhypbb = ', fxyhypbb
687 write(
lunout,*)
' dzoomxx = ', dzoomxx
688 write(
lunout,*)
' dzoomy = ', dzoomyy
689 write(
lunout,*)
' tauxx = ', tauxx
690 write(
lunout,*)
' tauyy = ', tauyy
732 'conf_gcm: *** ATTENTION !! grossismx < 1 . *** '
739 write(
lunout,*)
'conf_gcm: ***ATTENTION !! grossismy < 1 . *** '
787 CALL getin(
'tauy',tauy)
796 CALL getin(
'ysinus',ysinus)
807 'WARNING : option offline does not work with adjust=y :'
808 WRITE(
lunout,*)
'the files defstoke.nc, fluxstoke.nc ', &
809 'and fluxstokev.nc will not be created'
811 'only the file phystoke.nc will still be created '
868 write(
lunout,*)
'WARNING !!! '
869 write(
lunout,*)
"Le zoom en longitude est incompatible", &
870 " avec l'utilisation du filtre FFT ", &
871 "---> FFT filter not active"
894 CALL getin(
'vert_prof_dissip', vert_prof_dissip)
895 call assert(vert_prof_dissip == 0 .or. vert_prof_dissip == 1, &
896 "bad value for vert_prof_dissip")
903 ok_gradsfile = .
false.
904 CALL getin(
'ok_gradsfile',ok_gradsfile)
922 write(
lunout,*)
' #########################################'
923 write(
lunout,*)
' Configuration des parametres de cel0' &
926 write(
lunout,*)
' calend = ', calend
937 write(
lunout,*)
' lstardis = ', lstardis
957 write(
lunout,*)
' tauy = ', tauy
967 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