Ignore:
Timestamp:
Jun 4, 2015, 10:21:20 AM (10 years ago)
Author:
emillour
Message:

Updates in common dynamics (seq and ) to keep up with updates
in LMDZ5 (up to LMDZ5 trunk, rev 2250):

  • compilation:
  • added test in grid/dimension/makdim to check that # of longitudes is a multiple of 8
  • dyn3d_common:

Bug correction concerning zoom (cf LMDZ5 rev 2218)

  • coefpoly.F becomes coefpoly_m.F90 (in misc)
  • fxhyp.F => fxhyp_m.F90 , fyhyp.F => fyhyp_m.F90
  • new routines for zoom: invert_zoom_x_m.F90 and principal_cshift_m.F90
  • inigeom.F adapted to new zoom definition routines
  • fluxstokenc.F : got rid of calls to initial0()
  • dyn3d:
  • advtrac.F90 : got rid of calls to initial0()
  • conf_gcm.F90 : cosmetic changes and change in default dzoomx,dzoomy values
  • guide_mod.F90 : followed updates from Earth Model
  • gcm.F is now gcm.F90
  • dyn3dpar:
  • advtrac_p.F90, covcont_p.F90, mod_hallo.F90 : cosmetic changes
  • conf_gcm.F90 : cosmetic and changed in default dzoomx,dzoomy values
  • parallel_lmdz.F90 : updates to keep up with Earth model
  • misc:
  • arth.F90 becomes arth_m.F90
  • wxios.F90 updated wrt Earth model changes
  • nrtype.F90 and coefpoly_m.F90 added
  • ran1.F, sort.F, minmax.F, minmax2.F, juldate.F moved over from dyn3d_common

EM

Location:
trunk/LMDZ.COMMON/libf/dyn3d
Files:
4 edited
1 moved

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.COMMON/libf/dyn3d/advtrac.F90

    r1422 r1441  
    7474
    7575  IF(iadvtr.EQ.0) THEN
    76      CALL initial0(ijp1llm,pbaruc)
    77      CALL initial0(ijmllm,pbarvc)
     76     pbaruc(:,:)=0
     77     pbarvc(:,:)=0
    7878  ENDIF
    7979
  • trunk/LMDZ.COMMON/libf/dyn3d/conf_gcm.F90

    r1422 r1441  
    3434!     -metres  du zoom  avec  celles lues sur le fichier start .
    3535!
    36   LOGICAL etatinit
    37   INTEGER tapedef
     36  LOGICAL,INTENT(IN) :: etatinit
     37  INTEGER,INTENT(IN) :: tapedef
    3838
    3939!   Declarations :
     
    4444  include "iniprint.h"
    4545
    46 ! FH 2008/05/09 On elimine toutes les clefs physiques dans la dynamique
    47 ! #include "clesphys.h"
    48 !
    49 !
    5046!   local:
    5147!   ------
     
    858854     !Config  Help = extension en longitude  de la zone du zoom 
    859855     !Config         ( fraction de la zone totale)
    860      dzoomx = 0.0
     856     dzoomx = 0.2
    861857     CALL getin('dzoomx',dzoomx)
     858     call assert(dzoomx < 1, "conf_gcm: dzoomx must be < 1")
    862859
    863860     !Config  Key  = dzoomy
     
    866863     !Config  Help = extension en latitude de la zone  du zoom 
    867864     !Config         ( fraction de la zone totale)
    868      dzoomy = 0.0
     865     dzoomy = 0.2
    869866     CALL getin('dzoomy',dzoomy)
     867     call assert(dzoomy < 1, "conf_gcm: dzoomy must be < 1")
    870868
    871869     !Config  Key  = taux
  • trunk/LMDZ.COMMON/libf/dyn3d/fluxstokenc.F

    r1422 r1441  
    8080
    8181      IF(iadvtr.EQ.0) THEN
    82          CALL initial0(ijp1llm,phic)
    83          CALL initial0(ijp1llm,tetac)
    84          CALL initial0(ijp1llm,pbaruc)
    85          CALL initial0(ijmllm,pbarvc)
     82         phic(:,:)=0
     83         tetac(:,:)=0
     84         pbaruc(:,:)=0
     85         pbarvc(:,:)=0
    8686      ENDIF
    8787
  • trunk/LMDZ.COMMON/libf/dyn3d/gcm.F90

    r1440 r1441  
    22! $Id: gcm.F 1446 2010-10-22 09:27:25Z emillour $
    33!
    4 c
    5 c
    6       PROGRAM gcm
     4!
     5!
     6PROGRAM gcm
    77
    88#ifdef CPP_IOIPSL
    9       USE IOIPSL
     9  USE IOIPSL
    1010#else
    11 ! if not using IOIPSL, we still need to use (a local version of) getin
    12       USE ioipsl_getincom
     11  ! if not using IOIPSL, we still need to use (a local version of) getin
     12  USE ioipsl_getincom
    1313#endif
    1414
    1515
    1616#ifdef CPP_XIOS
    17     ! ug Pour les sorties XIOS
    18         USE wxios
    19 #endif
    20 
    21       USE filtreg_mod
    22       USE infotrac
    23       USE control_mod, only: planet_type,nday,day_step,iperiod,iphysiq,
    24      &                       raz_date,anneeref,starttime,dayref,
    25      &                       ok_dyn_ins,ok_dyn_ave,iecri,periodav,
    26      &                       less1day,fractday,ndynstep,nsplit_phys
    27       use cpdet_mod, only: ini_cpdet
    28       USE temps_mod, ONLY: calend,start_time,annee_ref,day_ref,
    29      .          itau_dyn,itau_phy,day_ini,jD_ref,jH_ref,day_end
     17  ! ug Pour les sorties XIOS
     18  USE wxios
     19#endif
     20
     21  USE filtreg_mod
     22  USE infotrac
     23  USE control_mod, only: planet_type,nday,day_step,iperiod,iphysiq, &
     24                             raz_date,anneeref,starttime,dayref,    &
     25                             ok_dyn_ins,ok_dyn_ave,iecri,periodav,  &
     26                             less1day,fractday,ndynstep,nsplit_phys
     27  use cpdet_mod, only: ini_cpdet
     28  USE temps_mod, ONLY: calend,start_time,annee_ref,day_ref, &
     29                itau_dyn,itau_phy,day_ini,jD_ref,jH_ref,day_end
    3030
    3131#ifdef INCA
    3232! Only INCA needs these informations (from the Earth's physics)
    33       USE indice_sol_mod
     33  USE indice_sol_mod
     34  USE mod_phys_lmdz_para, ONLY : klon_mpi_para_nb
    3435#endif
    3536
     
    4344!      USE comgeomphy, ONLY: initcomgeomphy
    4445#endif
    45 #ifdef INCA
    46       USE mod_phys_lmdz_para, ONLY : klon_mpi_para_nb
    47 #endif
    48       USE comconst_mod, ONLY: daysec,dtvr,dtphys,rad,g,r,cpp
    49       USE logic_mod, ONLY: read_start,iflag_phys,ok_guide,ecripar
     46
     47  USE comconst_mod, ONLY: daysec,dtvr,dtphys,rad,g,r,cpp
     48  USE logic_mod, ONLY: read_start,iflag_phys,ok_guide,ecripar
    5049
    5150!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    5251
    53       IMPLICIT NONE
    54 
    55 c      ......   Version  du 10/01/98    ..........
    56 
    57 c             avec  coordonnees  verticales hybrides
    58 c   avec nouveaux operat. dissipation * ( gradiv2,divgrad2,nxgraro2 )
    59 
    60 c=======================================================================
    61 c
    62 c   Auteur:  P. Le Van /L. Fairhead/F.Hourdin
    63 c   -------
    64 c
    65 c   Objet:
    66 c   ------
    67 c
    68 c   GCM LMD nouvelle grille
    69 c
    70 c=======================================================================
    71 c
    72 c  ... Dans inigeom , nouveaux calculs pour les elongations  cu , cv
    73 c      et possibilite d'appeler une fonction f(y)  a derivee tangente
    74 c      hyperbolique a la  place de la fonction a derivee sinusoidale.
    75 c  ... Possibilite de choisir le schema pour l'advection de
    76 c        q  , en modifiant iadv dans traceur.def  (MAF,10/02) .
    77 c
    78 c      Pour Van-Leer + Vapeur d'eau saturee, iadv(1)=4. (F.Codron,10/99)
    79 c      Pour Van-Leer iadv=10
    80 c
    81 c-----------------------------------------------------------------------
    82 c   Declarations:
    83 c   -------------
    84 
    85 #include "dimensions.h"
    86 #include "paramet.h"
    87 #include "comdissnew.h"
    88 #include "comgeom.h"
     52  IMPLICIT NONE
     53
     54  !      ......   Version  du 10/01/98    ..........
     55
     56  !             avec  coordonnees  verticales hybrides
     57  !   avec nouveaux operat. dissipation * ( gradiv2,divgrad2,nxgraro2 )
     58
     59  !=======================================================================
     60  !
     61  !   Auteur:  P. Le Van /L. Fairhead/F.Hourdin
     62  !   -------
     63  !
     64  !   Objet:
     65  !   ------
     66  !
     67  !   GCM LMD nouvelle grille
     68  !
     69  !=======================================================================
     70  !
     71  !  ... Dans inigeom , nouveaux calculs pour les elongations  cu , cv
     72  !      et possibilite d'appeler une fonction f(y)  a derivee tangente
     73  !      hyperbolique a la  place de la fonction a derivee sinusoidale.
     74  !  ... Possibilite de choisir le schema pour l'advection de
     75  !        q  , en modifiant iadv dans traceur.def  (MAF,10/02) .
     76  !
     77  !      Pour Van-Leer + Vapeur d'eau saturee, iadv(1)=4. (F.Codron,10/99)
     78  !      Pour Van-Leer iadv=10
     79  !
     80  !-----------------------------------------------------------------------
     81  !   Declarations:
     82  !   -------------
     83
     84  include "dimensions.h"
     85  include "paramet.h"
     86  include "comdissnew.h"
     87  include "comgeom.h"
    8988!!!!!!!!!!!#include "control.h"
    9089!#include "com_io_dyn.h"
    91 #include "iniprint.h"
    92 #include "tracstoke.h"
     90  include "iniprint.h"
     91  include "tracstoke.h"
    9392#ifdef INCA
    9493! Only INCA needs these informations (from the Earth's physics)
     
    9796
    9897
    99       REAL zdtvr
    100 
    101 c   variables dynamiques
    102       REAL vcov(ip1jm,llm),ucov(ip1jmp1,llm) ! vents covariants
    103       REAL teta(ip1jmp1,llm)                 ! temperature potentielle
    104       REAL, ALLOCATABLE, DIMENSION(:,:,:):: q! champs advectes
    105       REAL ps(ip1jmp1)                       ! pression  au sol
    106       REAL p (ip1jmp1,llmp1  )               ! pression aux interfac.des couches
    107       REAL masse(ip1jmp1,llm)                ! masse d'air
    108       REAL phis(ip1jmp1)                     ! geopotentiel au sol
    109       REAL phi(ip1jmp1,llm)                  ! geopotentiel
    110       REAL w(ip1jmp1,llm)                    ! vitesse verticale
    111 
    112 c variables dynamiques intermediaire pour le transport
    113 
    114 c   variables pour le fichier histoire
    115       REAL dtav      ! intervalle de temps elementaire
    116 
    117       REAL time_0
    118 
    119       LOGICAL lafin
    120       INTEGER ij,iq,l,i,j
    121 
    122 
    123       real time_step, t_wrt, t_ops
    124 
    125       LOGICAL first
    126 
    127 !      LOGICAL call_iniphys
    128 !      data call_iniphys/.true./
    129 
    130 c+jld variables test conservation energie
    131 c      REAL ecin(ip1jmp1,llm),ecin0(ip1jmp1,llm)
    132 C     Tendance de la temp. potentiel d (theta)/ d t due a la
    133 C     tansformation d'energie cinetique en energie thermique
    134 C     cree par la dissipation
    135       REAL dhecdt(ip1jmp1,llm)
    136 c      REAL vcont(ip1jm,llm),ucont(ip1jmp1,llm)
    137 c      REAL      d_h_vcol, d_qt, d_qw, d_ql, d_ec
    138       CHARACTER (len=15) :: ztit
    139 c-jld
    140 
    141 
    142       character (len=80) :: dynhist_file, dynhistave_file
    143       character (len=20) :: modname
    144       character (len=80) :: abort_message
    145 ! locales pour gestion du temps
    146       INTEGER :: an, mois, jour
    147       REAL :: heure
    148 
    149 
    150 c-----------------------------------------------------------------------
    151 c    variables pour l'initialisation de la physique :
    152 c    ------------------------------------------------
    153 !      INTEGER ngridmx
    154 !      PARAMETER( ngridmx = 2+(jjm-1)*iim - 1/jjm   )
    155 !      REAL zcufi(ngridmx),zcvfi(ngridmx)
    156 !      REAL latfi(ngridmx),lonfi(ngridmx)
    157 !      REAL airefi(ngridmx)
    158 !      SAVE latfi, lonfi, airefi
    159 
    160 c-----------------------------------------------------------------------
    161 c   Initialisations:
    162 c   ----------------
    163 
    164       abort_message = 'last timestep reached'
    165       modname = 'gcm'
    166       lafin    = .FALSE.
    167       dynhist_file = 'dyn_hist.nc'
    168       dynhistave_file = 'dyn_hist_ave.nc'
    169 
    170 
    171 
    172 c----------------------------------------------------------------------
    173 c  lecture des fichiers gcm.def ou run.def
    174 c  ---------------------------------------
    175 c
    176 ! Ehouarn: dump possibility of using defrun
    177 !#ifdef CPP_IOIPSL
    178       CALL conf_gcm( 99, .TRUE. )
    179       if (mod(iphysiq, iperiod) /= 0) call abort_gcm("conf_gcm",
    180      s "iphysiq must be a multiple of iperiod", 1)
    181 !#else
    182 !      CALL defrun( 99, .TRUE. , clesphy0 )
    183 !#endif
     98  REAL zdtvr
     99
     100  !   variables dynamiques
     101  REAL vcov(ip1jm,llm),ucov(ip1jmp1,llm) ! vents covariants
     102  REAL teta(ip1jmp1,llm)                 ! temperature potentielle
     103  REAL, ALLOCATABLE, DIMENSION(:,:,:):: q! champs advectes
     104  REAL ps(ip1jmp1)                       ! pression  au sol
     105  REAL p (ip1jmp1,llmp1  )               ! pression aux interfac.des couches
     106  REAL masse(ip1jmp1,llm)                ! masse d'air
     107  REAL phis(ip1jmp1)                     ! geopotentiel au sol
     108  REAL phi(ip1jmp1,llm)                  ! geopotentiel
     109  REAL w(ip1jmp1,llm)                    ! vitesse verticale
     110
     111  ! variables dynamiques intermediaire pour le transport
     112
     113  !   variables pour le fichier histoire
     114  REAL dtav      ! intervalle de temps elementaire
     115
     116  REAL time_0
     117
     118  LOGICAL lafin
     119  INTEGER ij,iq,l,i,j
     120
     121
     122  real time_step, t_wrt, t_ops
     123
     124  LOGICAL first
     125
     126  !      LOGICAL call_iniphys
     127  !      data call_iniphys/.true./
     128
     129  !+jld variables test conservation energie
     130  !      REAL ecin(ip1jmp1,llm),ecin0(ip1jmp1,llm)
     131  !     Tendance de la temp. potentiel d (theta)/ d t due a la
     132  !     tansformation d'energie cinetique en energie thermique
     133  !     cree par la dissipation
     134  REAL dhecdt(ip1jmp1,llm)
     135  !      REAL vcont(ip1jm,llm),ucont(ip1jmp1,llm)
     136  !      REAL      d_h_vcol, d_qt, d_qw, d_ql, d_ec
     137  CHARACTER (len=15) :: ztit
     138  !-jld
     139
     140
     141  character (len=80) :: dynhist_file, dynhistave_file
     142  character (len=20) :: modname
     143  character (len=80) :: abort_message
     144  ! locales pour gestion du temps
     145  INTEGER :: an, mois, jour
     146  REAL :: heure
     147  logical use_filtre_fft
     148
     149!-----------------------------------------------------------------------
     150!   Initialisations:
     151!   ----------------
     152
     153  abort_message = 'last timestep reached'
     154  modname = 'gcm'
     155  lafin    = .FALSE.
     156  dynhist_file = 'dyn_hist.nc'
     157  dynhistave_file = 'dyn_hist_ave.nc'
     158
     159
     160
     161!----------------------------------------------------------------------
     162!  lecture des fichiers gcm.def ou run.def
     163!  ---------------------------------------
     164!
     165  CALL conf_gcm( 99, .TRUE. )
     166  if (mod(iphysiq, iperiod) /= 0) call abort_gcm("conf_gcm", &
     167       "iphysiq must be a multiple of iperiod", 1)
     168
     169  use_filtre_fft=.FALSE.
     170  CALL getin('use_filtre_fft',use_filtre_fft)
     171  IF (use_filtre_fft) call abort_gcm('FFT filter is not available in the ' &
     172          // 'sequential version of the dynamics.', 1)
    184173
    185174!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     
    188177
    189178#ifdef CPP_XIOS
    190         CALL wxios_init("LMDZ")
     179  CALL wxios_init("LMDZ")
    191180#endif
    192181
     
    197186! dynamique -> physique pour l'initialisation
    198187#ifdef CPP_PHYS
    199       CALL init_phys_lmdz(iim,jjp1,llm,1,(/(jjm-1)*iim+2/))
     188  CALL init_phys_lmdz(iim,jjp1,llm,1,(/(jjm-1)*iim+2/))
    200189!      call initcomgeomphy ! now done in iniphysiq
    201190#endif
    202191!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    203 c
    204 c Initialisations pour Cp(T) Venus
    205       call ini_cpdet
    206 c
    207 c-----------------------------------------------------------------------
    208 c   Choix du calendrier
    209 c   -------------------
    210 
    211 c      calend = 'earth_365d'
     192!
     193! Initialisations pour Cp(T) Venus
     194  call ini_cpdet
     195!
     196!-----------------------------------------------------------------------
     197!   Choix du calendrier
     198!   -------------------
     199
     200!      calend = 'earth_365d'
    212201
    213202#ifdef CPP_IOIPSL
    214       if (calend == 'earth_360d') then
    215         call ioconf_calendar('360d')
    216         write(lunout,*)'CALENDRIER CHOISI: Terrestre a 360 jours/an'
    217       else if (calend == 'earth_365d') then
    218         call ioconf_calendar('noleap')
    219         write(lunout,*)'CALENDRIER CHOISI: Terrestre a 365 jours/an'
    220       else if (calend == 'earth_366d') then
    221         call ioconf_calendar('gregorian')
    222         write(lunout,*)'CALENDRIER CHOISI: Terrestre bissextile'
    223       else if (calend == 'titan') then
     203  if (calend == 'earth_360d') then
     204    call ioconf_calendar('360d')
     205    write(lunout,*)'CALENDRIER CHOISI: Terrestre a 360 jours/an'
     206  else if (calend == 'earth_365d') then
     207    call ioconf_calendar('noleap')
     208    write(lunout,*)'CALENDRIER CHOISI: Terrestre a 365 jours/an'
     209  else if (calend == 'earth_366d') then
     210    call ioconf_calendar('gregorian')
     211    write(lunout,*)'CALENDRIER CHOISI: Terrestre bissextile'
     212  else if (calend == 'titan') then
    224213!        call ioconf_calendar('titan')
    225         write(lunout,*)'CALENDRIER CHOISI: Titan'
    226         abort_message = 'A FAIRE...'
    227         call abort_gcm(modname,abort_message,1)
    228       else if (calend == 'venus') then
     214    write(lunout,*)'CALENDRIER CHOISI: Titan'
     215    abort_message = 'A FAIRE...'
     216    call abort_gcm(modname,abort_message,1)
     217  else if (calend == 'venus') then
    229218!        call ioconf_calendar('venus')
    230         write(lunout,*)'CALENDRIER CHOISI: Venus'
    231         abort_message = 'A FAIRE...'
    232         call abort_gcm(modname,abort_message,1)
    233       else
    234         abort_message = 'Mauvais choix de calendrier'
    235         call abort_gcm(modname,abort_message,1)
    236       endif
    237 #endif
    238 c-----------------------------------------------------------------------
    239 
    240       IF (type_trac == 'inca') THEN
     219    write(lunout,*)'CALENDRIER CHOISI: Venus'
     220    abort_message = 'A FAIRE...'
     221    call abort_gcm(modname,abort_message,1)
     222  else
     223    abort_message = 'Mauvais choix de calendrier'
     224    call abort_gcm(modname,abort_message,1)
     225  endif
     226#endif
     227!-----------------------------------------------------------------------
     228
     229  IF (type_trac == 'inca') THEN
    241230#ifdef INCA
    242       call init_const_lmdz(nbtr,anneeref,dayref,iphysiq,day_step,nday,
    243      $        nbsrf, is_oce,is_sic,is_ter,is_lic)
    244       call init_inca_para(iim,jjm+1,klon,1,klon_mpi_para_nb,0)
    245 #endif
    246       END IF
    247 c
    248 c
    249 c------------------------------------
    250 c   Initialisation partie parallele
    251 c------------------------------------
    252 
    253 c
    254 c
    255 c-----------------------------------------------------------------------
    256 c   Initialisation des traceurs
    257 c   ---------------------------
    258 c  Choix du nombre de traceurs et du schema pour l'advection
    259 c  dans fichier traceur.def, par default ou via INCA
    260       call infotrac_init
    261 
    262 c Allocation de la tableau q : champs advectes   
    263       allocate(q(ip1jmp1,llm,nqtot))
    264 
    265 c-----------------------------------------------------------------------
    266 c   Lecture de l'etat initial :
    267 c   ---------------------------
    268 
    269 c  lecture du fichier start.nc
    270       if (read_start) then
    271       ! we still need to run iniacademic to initialize some
    272       ! constants & fields, if we run the 'newtonian' or 'SW' cases:
    273         if (iflag_phys.ne.1) then
    274           CALL iniacademic(vcov,ucov,teta,q,masse,ps,phis,time_0)
    275         endif
    276 
    277         CALL dynetat0("start.nc",vcov,ucov,
    278      &              teta,q,masse,ps,phis, time_0)
     231    call init_const_lmdz(nbtr,anneeref,dayref,iphysiq,day_step,nday, &
     232         nbsrf, is_oce,is_sic,is_ter,is_lic)
     233    call init_inca_para(iim,jjm+1,klon,1,klon_mpi_para_nb,0)
     234#endif
     235  END IF
     236  !
     237  !
     238  !------------------------------------
     239  !   Initialisation partie parallele
     240  !------------------------------------
     241
     242  !
     243  !
     244  !-----------------------------------------------------------------------
     245  !   Initialisation des traceurs
     246  !   ---------------------------
     247  !  Choix du nombre de traceurs et du schema pour l'advection
     248  !  dans fichier traceur.def, par default ou via INCA
     249  call infotrac_init
     250
     251  ! Allocation de la tableau q : champs advectes   
     252  allocate(q(ip1jmp1,llm,nqtot))
     253
     254  !-----------------------------------------------------------------------
     255  !   Lecture de l'etat initial :
     256  !   ---------------------------
     257
     258  !  lecture du fichier start.nc
     259  if (read_start) then
     260     ! we still need to run iniacademic to initialize some
     261     ! constants & fields, if we run the 'newtonian' or 'SW' cases:
     262     if (iflag_phys.ne.1) then
     263        CALL iniacademic(vcov,ucov,teta,q,masse,ps,phis,time_0)
     264     endif
     265
     266     CALL dynetat0("start.nc",vcov,ucov, &
     267                    teta,q,masse,ps,phis, time_0)
    279268       
    280         ! Load relaxation fields (simple nudging). AS 09/2013
    281         ! ---------------------------------------------------
    282         if (planet_type.eq."generic") then
    283          if (ok_guide) then
    284            CALL relaxetat0("relax.nc")
    285          endif
    286         endif
     269     ! Load relaxation fields (simple nudging). AS 09/2013
     270     ! ---------------------------------------------------
     271     if (planet_type.eq."generic") then
     272       if (ok_guide) then
     273         CALL relaxetat0("relax.nc")
     274       endif
     275     endif
    287276 
    288 c       write(73,*) 'ucov',ucov
    289 c       write(74,*) 'vcov',vcov
    290 c       write(75,*) 'teta',teta
    291 c       write(76,*) 'ps',ps
    292 c       write(77,*) 'q',q
    293 
    294       endif ! of if (read_start)
    295 
    296       IF (type_trac == 'inca') THEN
     277     !       write(73,*) 'ucov',ucov
     278     !       write(74,*) 'vcov',vcov
     279     !       write(75,*) 'teta',teta
     280     !       write(76,*) 'ps',ps
     281     !       write(77,*) 'q',q
     282
     283  endif ! of if (read_start)
     284
     285  IF (type_trac == 'inca') THEN
    297286#ifdef INCA
    298          call init_inca_dim(klon,llm,iim,jjm,
    299      $        rlonu,rlatu,rlonv,rlatv)
    300 #endif
    301       END IF
    302 
    303 
    304 c le cas echeant, creation d un etat initial
    305       IF (prt_level > 9) WRITE(lunout,*)
    306      .              'GCM: AVANT iniacademic AVANT AVANT AVANT AVANT'
    307       if (.not.read_start) then
    308          CALL iniacademic(vcov,ucov,teta,q,masse,ps,phis,time_0)
    309       endif
    310 
    311 
    312 c-----------------------------------------------------------------------
    313 c   Lecture des parametres de controle pour la simulation :
    314 c   -------------------------------------------------------
    315 c  on recalcule eventuellement le pas de temps
    316 
    317       IF(MOD(day_step,iperiod).NE.0) THEN
    318         abort_message =
    319      .  'Il faut choisir un nb de pas par jour multiple de iperiod'
    320         call abort_gcm(modname,abort_message,1)
    321       ENDIF
    322 
    323       IF(MOD(day_step,iphysiq).NE.0) THEN
    324         abort_message =
    325      * 'Il faut choisir un nb de pas par jour multiple de iphysiq'
    326         call abort_gcm(modname,abort_message,1)
    327       ENDIF
    328 
    329       zdtvr    = daysec/REAL(day_step)
    330         IF(dtvr.NE.zdtvr) THEN
    331          WRITE(lunout,*)
    332      .    'WARNING!!! changement de pas de temps',dtvr,'>',zdtvr
    333         ENDIF
    334 
    335 C
    336 C on remet le calendrier à zero si demande
    337 c
    338       IF (start_time /= starttime) then
    339         WRITE(lunout,*)' GCM: Attention l''heure de depart lue dans le'
    340      &,' fichier restart ne correspond pas à celle lue dans le run.def'
    341         IF (raz_date == 1) then
    342           WRITE(lunout,*)'Je prends l''heure lue dans run.def'
    343           start_time = starttime
    344         ELSE
    345           call abort_gcm("gcm", "'Je m''arrete'", 1)
    346         ENDIF
    347       ENDIF
    348       IF (raz_date == 1) THEN
    349         annee_ref = anneeref
    350         day_ref = dayref
    351         day_ini = dayref
    352         itau_dyn = 0
    353         itau_phy = 0
    354         time_0 = 0.
    355         write(lunout,*)
    356      .   'GCM: On reinitialise a la date lue dans gcm.def'
    357       ELSE IF (annee_ref .ne. anneeref .or. day_ref .ne. dayref) THEN
    358         write(lunout,*)
    359      .  'GCM: Attention les dates initiales lues dans le fichier'
    360         write(lunout,*)
    361      .  ' restart ne correspondent pas a celles lues dans '
    362         write(lunout,*)' gcm.def'
    363         write(lunout,*)' annee_ref=',annee_ref," anneeref=",anneeref
    364         write(lunout,*)' day_ref=',day_ref," dayref=",dayref
    365         write(lunout,*)' Pas de remise a zero'
    366       ENDIF
    367 
    368 c      if (annee_ref .ne. anneeref .or. day_ref .ne. dayref) then
    369 c        write(lunout,*)
    370 c     .  'GCM: Attention les dates initiales lues dans le fichier'
    371 c        write(lunout,*)
    372 c     .  ' restart ne correspondent pas a celles lues dans '
    373 c        write(lunout,*)' gcm.def'
    374 c        write(lunout,*)' annee_ref=',annee_ref," anneeref=",anneeref
    375 c        write(lunout,*)' day_ref=',day_ref," dayref=",dayref
    376 c        if (raz_date .ne. 1) then
    377 c          write(lunout,*)
    378 c     .    'GCM: On garde les dates du fichier restart'
    379 c        else
    380 c          annee_ref = anneeref
    381 c          day_ref = dayref
    382 c          day_ini = dayref
    383 c          itau_dyn = 0
    384 c          itau_phy = 0
    385 c          time_0 = 0.
    386 c          write(lunout,*)
    387 c     .   'GCM: On reinitialise a la date lue dans gcm.def'
    388 c        endif
    389 c      ELSE
    390 c        raz_date = 0
    391 c      endif
     287     call init_inca_dim(klon,llm,iim,jjm, &
     288          rlonu,rlatu,rlonv,rlatv)
     289#endif
     290  END IF
     291
     292
     293  ! le cas echeant, creation d un etat initial
     294  IF (prt_level > 9) WRITE(lunout,*) &
     295       'GCM: AVANT iniacademic AVANT AVANT AVANT AVANT'
     296  if (.not.read_start) then
     297     CALL iniacademic(vcov,ucov,teta,q,masse,ps,phis,time_0)
     298  endif
     299
     300
     301  !-----------------------------------------------------------------------
     302  !   Lecture des parametres de controle pour la simulation :
     303  !   -------------------------------------------------------
     304  !  on recalcule eventuellement le pas de temps
     305
     306  IF(MOD(day_step,iperiod).NE.0) THEN
     307     abort_message = &
     308       'Il faut choisir un nb de pas par jour multiple de iperiod'
     309     call abort_gcm(modname,abort_message,1)
     310  ENDIF
     311
     312  IF(MOD(day_step,iphysiq).NE.0) THEN
     313     abort_message = &
     314       'Il faut choisir un nb de pas par jour multiple de iphysiq'
     315     call abort_gcm(modname,abort_message,1)
     316  ENDIF
     317
     318  zdtvr    = daysec/REAL(day_step)
     319  IF(dtvr.NE.zdtvr) THEN
     320     WRITE(lunout,*) &
     321          'WARNING!!! changement de pas de temps',dtvr,'>',zdtvr
     322  ENDIF
     323
     324  !
     325  ! on remet le calendrier à zero si demande
     326  !
     327  IF (start_time /= starttime) then
     328     WRITE(lunout,*)' GCM: Attention l''heure de depart lue dans le' &
     329     ,' fichier restart ne correspond pas à celle lue dans le run.def'
     330     IF (raz_date == 1) then
     331        WRITE(lunout,*)'Je prends l''heure lue dans run.def'
     332        start_time = starttime
     333     ELSE
     334        call abort_gcm("gcm", "'Je m''arrete'", 1)
     335     ENDIF
     336  ENDIF
     337  IF (raz_date == 1) THEN
     338     annee_ref = anneeref
     339     day_ref = dayref
     340     day_ini = dayref
     341     itau_dyn = 0
     342     itau_phy = 0
     343     time_0 = 0.
     344     write(lunout,*) &
     345         'GCM: On reinitialise a la date lue dans gcm.def'
     346  ELSE IF (annee_ref .ne. anneeref .or. day_ref .ne. dayref) THEN
     347     write(lunout,*) &
     348        'GCM: Attention les dates initiales lues dans le fichier'
     349     write(lunout,*) &
     350        ' restart ne correspondent pas a celles lues dans '
     351     write(lunout,*)' gcm.def'
     352     write(lunout,*)' annee_ref=',annee_ref," anneeref=",anneeref
     353     write(lunout,*)' day_ref=',day_ref," dayref=",dayref
     354     write(lunout,*)' Pas de remise a zero'
     355  ENDIF
     356
     357!      if (annee_ref .ne. anneeref .or. day_ref .ne. dayref) then
     358!        write(lunout,*)
     359!     .  'GCM: Attention les dates initiales lues dans le fichier'
     360!        write(lunout,*)
     361!     .  ' restart ne correspondent pas a celles lues dans '
     362!        write(lunout,*)' gcm.def'
     363!        write(lunout,*)' annee_ref=',annee_ref," anneeref=",anneeref
     364!        write(lunout,*)' day_ref=',day_ref," dayref=",dayref
     365!        if (raz_date .ne. 1) then
     366!          write(lunout,*)
     367!     .    'GCM: On garde les dates du fichier restart'
     368!        else
     369!          annee_ref = anneeref
     370!          day_ref = dayref
     371!          day_ini = dayref
     372!          itau_dyn = 0
     373!          itau_phy = 0
     374!          time_0 = 0.
     375!          write(lunout,*)
     376!     .   'GCM: On reinitialise a la date lue dans gcm.def'
     377!        endif
     378!      ELSE
     379!        raz_date = 0
     380!      endif
    392381
    393382#ifdef CPP_IOIPSL
    394       mois = 1
    395       heure = 0.
     383  mois = 1
     384  heure = 0.
    396385! Ce n'est defini pour l'instant que pour la Terre...
    397       if (planet_type.eq.'earth') then
    398       call ymds2ju(annee_ref, mois, day_ref, heure, jD_ref)
    399       jH_ref = jD_ref - int(jD_ref)
    400       jD_ref = int(jD_ref)
    401 
    402       call ioconf_startdate(INT(jD_ref), jH_ref)
    403 
    404       write(lunout,*)'DEBUG'
    405       write(lunout,*)'annee_ref, mois, day_ref, heure, jD_ref'
    406       write(lunout,*)annee_ref, mois, day_ref, heure, jD_ref
    407       call ju2ymds(jD_ref+jH_ref,an, mois, jour, heure)
    408       write(lunout,*)'jD_ref+jH_ref,an, mois, jour, heure'
    409       write(lunout,*)jD_ref+jH_ref,an, mois, jour, heure
    410       else
     386  if (planet_type.eq.'earth') then
     387    call ymds2ju(annee_ref, mois, day_ref, heure, jD_ref)
     388    jH_ref = jD_ref - int(jD_ref)
     389    jD_ref = int(jD_ref)
     390
     391    call ioconf_startdate(INT(jD_ref), jH_ref)
     392
     393    write(lunout,*)'DEBUG'
     394    write(lunout,*)'annee_ref, mois, day_ref, heure, jD_ref'
     395    write(lunout,*)annee_ref, mois, day_ref, heure, jD_ref
     396    call ju2ymds(jD_ref+jH_ref,an, mois, jour, heure)
     397    write(lunout,*)'jD_ref+jH_ref,an, mois, jour, heure'
     398    write(lunout,*)jD_ref+jH_ref,an, mois, jour, heure
     399  else
    411400! A voir pour Titan et Venus
    412         jD_ref=0
    413         jH_ref=0
    414       write(lunout,*)'A VOIR POUR VENUS ET TITAN: jD_ref, jH_ref'
    415       write(lunout,*)jD_ref,jH_ref
    416       endif ! planet_type
     401    jD_ref=0
     402    jH_ref=0
     403    write(lunout,*)'A VOIR POUR VENUS ET TITAN: jD_ref, jH_ref'
     404    write(lunout,*)jD_ref,jH_ref
     405  endif ! planet_type
    417406#else
    418 ! Ehouarn: we still need to define JD_ref and JH_ref
    419 ! and since we don't know how many days there are in a year
    420 ! we set JD_ref to 0 (this should be improved ...)
    421       jD_ref=0
    422       jH_ref=0
    423 #endif
    424 
    425       if (iflag_phys.eq.1) then
    426       ! these initialisations have already been done (via iniacademic)
    427       ! if running in SW or Newtonian mode
    428 c-----------------------------------------------------------------------
    429 c   Initialisation des constantes dynamiques :
    430 c   ------------------------------------------
    431         dtvr = zdtvr
    432         CALL iniconst
    433 
    434 c-----------------------------------------------------------------------
    435 c   Initialisation de la geometrie :
    436 c   --------------------------------
    437         CALL inigeom
    438 
    439 c-----------------------------------------------------------------------
    440 c   Initialisation du filtre :
    441 c   --------------------------
    442         CALL inifilr
    443       endif ! of if (iflag_phys.eq.1)
    444 c
    445 c-----------------------------------------------------------------------
    446 c   Initialisation de la dissipation :
    447 c   ----------------------------------
    448 
    449       CALL inidissip( lstardis, nitergdiv, nitergrot, niterh   ,
    450      *                tetagdiv, tetagrot , tetatemp, vert_prof_dissip)
    451 
    452 c-----------------------------------------------------------------------
    453 c   Initialisation de la physique :
    454 c   -------------------------------
    455 
    456       IF ((iflag_phys==1).or.(iflag_phys>=100)) THEN
    457 !      IF (call_iniphys.and.(iflag_phys==1.or.iflag_phys>=100)) THEN
    458 !         latfi(1)=rlatu(1)
    459 !         lonfi(1)=0.
    460 !         zcufi(1) = cu(1)
    461 !         zcvfi(1) = cv(1)
    462 !         DO j=2,jjm
    463 !            DO i=1,iim
    464 !               latfi((j-2)*iim+1+i)= rlatu(j)
    465 !               lonfi((j-2)*iim+1+i)= rlonv(i)
    466 !               zcufi((j-2)*iim+1+i) = cu((j-1)*iip1+i)
    467 !               zcvfi((j-2)*iim+1+i) = cv((j-1)*iip1+i)
    468 !            ENDDO
    469 !         ENDDO
    470 !         latfi(ngridmx)= rlatu(jjp1)
    471 !         lonfi(ngridmx)= 0.
    472 !         zcufi(ngridmx) = cu(ip1jm+1)
    473 !         zcvfi(ngridmx) = cv(ip1jm-iim)
    474 
    475          ! build airefi(), mesh area on physics grid
    476 !         CALL gr_dyn_fi(1,iip1,jjp1,ngridmx,aire,airefi)
    477          ! Poles are single points on physics grid
    478 !         airefi(1)=airefi(1)*iim
    479 !         airefi(ngridmx)=airefi(ngridmx)*iim
    480 
    481 ! Initialisation de la physique: pose probleme quand on tourne
    482 ! SANS physique, car iniphysiq.F est dans le repertoire phy[]...
    483 ! Il faut une cle CPP_PHYS
     407  ! Ehouarn: we still need to define JD_ref and JH_ref
     408  ! and since we don't know how many days there are in a year
     409  ! we set JD_ref to 0 (this should be improved ...)
     410  jD_ref=0
     411  jH_ref=0
     412#endif
     413
     414  if (iflag_phys.eq.1) then
     415     ! these initialisations have already been done (via iniacademic)
     416     ! if running in SW or Newtonian mode
     417     !-----------------------------------------------------------------------
     418     !   Initialisation des constantes dynamiques :
     419     !   ------------------------------------------
     420     dtvr = zdtvr
     421     CALL iniconst
     422
     423     !-----------------------------------------------------------------------
     424     !   Initialisation de la geometrie :
     425     !   --------------------------------
     426     CALL inigeom
     427
     428     !-----------------------------------------------------------------------
     429     !   Initialisation du filtre :
     430     !   --------------------------
     431     CALL inifilr
     432  endif ! of if (iflag_phys.eq.1)
     433  !
     434  !-----------------------------------------------------------------------
     435  !   Initialisation de la dissipation :
     436  !   ----------------------------------
     437
     438  CALL inidissip( lstardis, nitergdiv, nitergrot, niterh   , &
     439                  tetagdiv, tetagrot , tetatemp, vert_prof_dissip)
     440
     441  !-----------------------------------------------------------------------
     442  !   Initialisation de la physique :
     443  !   -------------------------------
     444
     445  IF ((iflag_phys==1).or.(iflag_phys>=100)) THEN
     446     ! Physics:
    484447#ifdef CPP_PHYS
    485 !         CALL iniphysiq(ngridmx,llm,daysec,day_ini,dtphys/nsplit_phys,
    486 !     &                latfi,lonfi,airefi,zcufi,zcvfi,rad,g,r,cpp,
    487 !     &                iflag_phys)
    488          CALL iniphysiq(iim,jjm,llm,daysec,day_ini,dtphys/nsplit_phys,
    489      &                rlatu,rlonv,aire,cu,cv,rad,g,r,cpp,
    490      &                iflag_phys)
    491 #endif
    492 !         call_iniphys=.false.
    493       ENDIF ! of IF ((iflag_phys==1).or.(iflag_phys>=100))
    494 
    495 c  numero de stockage pour les fichiers de redemarrage:
    496 
    497 c-----------------------------------------------------------------------
    498 c   Initialisation des I/O :
    499 c   ------------------------
    500 
    501       if (nday>=0) then ! standard case
    502         day_end=day_ini+nday
    503       else ! special case when nday <0, run -nday dynamical steps
    504         day_end=day_ini-nday/day_step
    505       endif
    506       if (less1day) then
    507         day_end=day_ini+floor(time_0+fractday)
    508       endif
    509       if (ndynstep.gt.0) then
    510         day_end=day_ini+floor(time_0+float(ndynstep)/float(day_step))
    511       endif
     448         CALL iniphysiq(iim,jjm,llm,daysec,day_ini,dtphys/nsplit_phys, &
     449                      rlatu,rlonv,aire,cu,cv,rad,g,r,cpp, &
     450                      iflag_phys)
     451#endif
     452  ENDIF ! of IF ((iflag_phys==1).or.(iflag_phys>=100))
     453
     454  !-----------------------------------------------------------------------
     455  !   Initialisation des I/O :
     456  !   ------------------------
     457
     458  if (nday>=0) then ! standard case
     459     day_end=day_ini+nday
     460  else ! special case when nday <0, run -nday dynamical steps
     461     day_end=day_ini-nday/day_step
     462  endif
     463  if (less1day) then
     464     day_end=day_ini+floor(time_0+fractday)
     465  endif
     466  if (ndynstep.gt.0) then
     467     day_end=day_ini+floor(time_0+float(ndynstep)/float(day_step))
     468  endif
    512469     
    513       WRITE(lunout,'(a,i7,a,i7)')
    514      &             "run from day ",day_ini,"  to day",day_end
     470  WRITE(lunout,'(a,i7,a,i7)') &
     471               "run from day ",day_ini,"  to day",day_end
    515472
    516473#ifdef CPP_IOIPSL
    517 ! Ce n'est defini pour l'instant que pour la Terre...
    518       if (planet_type.eq.'earth') then
    519       call ju2ymds(jD_ref + day_ini - day_ref, an, mois, jour, heure)
    520       write (lunout,301)jour, mois, an
    521       call ju2ymds(jD_ref + day_end - day_ref, an, mois, jour, heure)
    522       write (lunout,302)jour, mois, an
    523       else
    524 ! A voir pour Titan et Venus
    525       write(lunout,*)'A VOIR POUR VENUS/TITAN: separation en annees...'
    526       endif ! planet_type
    527 
    528  301  FORMAT('1'/,15x,'run du ', i2,'/',i2,'/',i4)
    529  302  FORMAT('1'/,15x,'    au ', i2,'/',i2,'/',i4)
    530 #endif
    531 
    532       if (planet_type=="mars") then
    533         ! For Mars we transmit day_ini
    534         CALL dynredem0("restart.nc", day_ini, phis)
    535       else
    536         CALL dynredem0("restart.nc", day_end, phis)
    537       endif
    538       ecripar = .TRUE.
     474  ! Ce n'est defini pour l'instant que pour la Terre...
     475  if (planet_type.eq.'earth') then
     476    call ju2ymds(jD_ref + day_ini - day_ref, an, mois, jour, heure)
     477    write (lunout,301)jour, mois, an
     478    call ju2ymds(jD_ref + day_end - day_ref, an, mois, jour, heure)
     479    write (lunout,302)jour, mois, an
     480  else
     481  ! A voir pour Titan et Venus
     482    write(lunout,*)'A VOIR POUR VENUS/TITAN: separation en annees...'
     483  endif ! planet_type
     484301  FORMAT('1'/,15x,'run du ', i2,'/',i2,'/',i4)
     485302  FORMAT('1'/,15x,'    au ', i2,'/',i2,'/',i4)
     486#endif
     487
     488  if (planet_type=="mars") then
     489    ! For Mars we transmit day_ini
     490    CALL dynredem0("restart.nc", day_ini, phis)
     491  else
     492    CALL dynredem0("restart.nc", day_end, phis)
     493  endif
     494  ecripar = .TRUE.
    539495
    540496#ifdef CPP_IOIPSL
    541       time_step = zdtvr
    542       if (ok_dyn_ins) then
    543         ! initialize output file for instantaneous outputs
    544         ! t_ops = iecri * daysec ! do operations every t_ops
    545         t_ops =((1.0*iecri)/day_step) * daysec 
    546         t_wrt = daysec ! iecri * daysec ! write output every t_wrt
    547         CALL inithist(day_ref,annee_ref,time_step,
    548      &              t_ops,t_wrt)
    549       endif
    550 
    551       IF (ok_dyn_ave) THEN
    552         ! initialize output file for averaged outputs
    553         t_ops = iperiod * time_step ! do operations every t_ops
    554         t_wrt = periodav * daysec   ! write output every t_wrt
    555         CALL initdynav(day_ref,annee_ref,time_step,
    556      &       t_ops,t_wrt)
    557       END IF
    558       dtav = iperiod*dtvr/daysec
     497  time_step = zdtvr
     498  if (ok_dyn_ins) then
     499    ! initialize output file for instantaneous outputs
     500    ! t_ops = iecri * daysec ! do operations every t_ops
     501    t_ops =((1.0*iecri)/day_step) * daysec 
     502    t_wrt = daysec ! iecri * daysec ! write output every t_wrt
     503    CALL inithist(day_ref,annee_ref,time_step, &
     504                   t_ops,t_wrt)
     505  endif
     506
     507  IF (ok_dyn_ave) THEN
     508    ! initialize output file for averaged outputs
     509    t_ops = iperiod * time_step ! do operations every t_ops
     510    t_wrt = periodav * daysec   ! write output every t_wrt
     511    CALL initdynav(day_ref,annee_ref,time_step, &
     512            t_ops,t_wrt)
     513  END IF
     514  dtav = iperiod*dtvr/daysec
    559515#endif
    560516! #endif of #ifdef CPP_IOIPSL
    561517
    562 c  Choix des frequences de stokage pour le offline
    563 c      istdyn=day_step/4     ! stockage toutes les 6h=1jour/4
    564 c      istdyn=day_step/12     ! stockage toutes les 2h=1jour/12
    565       istdyn=day_step/4     ! stockage toutes les 6h=1jour/12
    566       istphy=istdyn/iphysiq     
    567 
    568 
    569 c
    570 c-----------------------------------------------------------------------
    571 c   Integration temporelle du modele :
    572 c   ----------------------------------
    573 
    574 c       write(78,*) 'ucov',ucov
    575 c       write(78,*) 'vcov',vcov
    576 c       write(78,*) 'teta',teta
    577 c       write(78,*) 'ps',ps
    578 c       write(78,*) 'q',q
    579 
    580 
    581       CALL leapfrog(ucov,vcov,teta,ps,masse,phis,q,
    582      .              time_0)
    583 
    584       END
    585 
     518  !  Choix des frequences de stokage pour le offline
     519  !      istdyn=day_step/4     ! stockage toutes les 6h=1jour/4
     520  !      istdyn=day_step/12     ! stockage toutes les 2h=1jour/12
     521  istdyn=day_step/4     ! stockage toutes les 6h=1jour/12
     522  istphy=istdyn/iphysiq     
     523
     524
     525  !
     526  !-----------------------------------------------------------------------
     527  !   Integration temporelle du modele :
     528  !   ----------------------------------
     529
     530  !       write(78,*) 'ucov',ucov
     531  !       write(78,*) 'vcov',vcov
     532  !       write(78,*) 'teta',teta
     533  !       write(78,*) 'ps',ps
     534  !       write(78,*) 'q',q
     535
     536
     537  CALL leapfrog(ucov,vcov,teta,ps,masse,phis,q,time_0)
     538
     539END PROGRAM gcm
     540
  • trunk/LMDZ.COMMON/libf/dyn3d/guide_mod.F90

    r1422 r1441  
    154154          rcod=nf90_open('apbp.nc',Nf90_NOWRITe, ncidpl)
    155155          if (rcod.NE.NF_NOERR) THEN
    156              print *,'Guide: probleme -> pas de fichier apbp.nc'
    157              CALL abort_gcm(modname,abort_message,1)
     156             CALL abort_gcm(modname, &
     157                  'Guide: probleme -> pas de fichier apbp.nc',1)
    158158          endif
    159159       endif
     
    163163               rcod=nf90_open('u.nc',Nf90_NOWRITe,ncidpl)
    164164               if (rcod.NE.NF_NOERR) THEN
    165                   print *,'Guide: probleme -> pas de fichier u.nc'
    166                   CALL abort_gcm(modname,abort_message,1)
     165                  CALL abort_gcm(modname, &
     166                       'Guide: probleme -> pas de fichier u.nc',1)
    167167               endif
    168168           endif
     
    171171               rcod=nf90_open('v.nc',nf90_nowrite,ncidpl)
    172172               if (rcod.NE.NF_NOERR) THEN
    173                   print *,'Guide: probleme -> pas de fichier v.nc'
    174                   CALL abort_gcm(modname,abort_message,1)
     173                  CALL abort_gcm(modname, &
     174                       'Guide: probleme -> pas de fichier v.nc',1)
    175175               endif
    176176           endif
     
    179179               rcod=nf90_open('T.nc',nf90_nowrite,ncidpl)
    180180               if (rcod.NE.NF_NOERR) THEN
    181                   print *,'Guide: probleme -> pas de fichier T.nc'
    182                   CALL abort_gcm(modname,abort_message,1)
     181                  CALL abort_gcm(modname, &
     182                       'Guide: probleme -> pas de fichier T.nc',1)
    183183               endif
    184184           endif
     
    187187               rcod=nf90_open('hur.nc',nf90_nowrite, ncidpl)
    188188               if (rcod.NE.NF_NOERR) THEN
    189                   print *,'Guide: probleme -> pas de fichier hur.nc'
    190                   CALL abort_gcm(modname,abort_message,1)
     189                  CALL abort_gcm(modname, &
     190                       'Guide: probleme -> pas de fichier hur.nc',1)
    191191               endif
    192192           endif
     
    196196    IF (error.NE.NF_NOERR) error=NF_INQ_DIMID(ncidpl,'PRESSURE',rid)
    197197    IF (error.NE.NF_NOERR) THEN
    198         print *,'Guide: probleme lecture niveaux pression'
    199         CALL abort_gcm(modname,abort_message,1)
     198        CALL abort_gcm(modname,'Guide: probleme lecture niveaux pression',1)
    200199    ENDIF
    201200    error=NF_INQ_DIMLEN(ncidpl,rid,nlevnc)
Note: See TracChangeset for help on using the changeset viewer.