Changeset 492 for trunk/LMDZ.COMMON/libf


Ignore:
Timestamp:
Jan 5, 2012, 8:28:41 AM (13 years ago)
Author:
emillour
Message:

Common dynamics: updates to keep up with LMDZ5 Earth (rev 1605)
See file "DOC/chantiers/commit_importants.log" for details.
EM

Location:
trunk/LMDZ.COMMON/libf
Files:
25 edited

Legend:

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

    r270 r492  
    2828  IMPLICIT NONE
    2929#ifndef CPP_EARTH
    30   WRITE(lunout,*)'limit_netcdf: Earth-specific routine, needs Earth physics'
     30  WRITE(*,*)'limit_netcdf: Earth-specific program, needs Earth physics'
    3131#else
    3232!-------------------------------------------------------------------------------
     
    6767#endif
    6868
    69   IF (config_inca /= 'none') THEN
     69  IF (type_trac == 'inca') THEN
    7070#ifdef INCA
    7171    CALL init_const_lmdz(nbtr,anneeref,dayref,iphysiq,day_step,nday)
  • trunk/LMDZ.COMMON/libf/dyn3d/conf_gcm.F

    r270 r492  
    1313      use ioipsl_getincom
    1414#endif
     15      USE infotrac, ONLY : type_trac
    1516      IMPLICIT NONE
    1617c-----------------------------------------------------------------------
     
    156157      nday = 10
    157158      CALL getin('nday',nday)
     159
     160!Config  Key  = starttime
     161!Config  Desc = Heure de depart de la simulation
     162!Config  Def  = 0
     163!Config  Help = Heure de depart de la simulation
     164!Config         en jour
     165      starttime = 0
     166      CALL getin('starttime',starttime)
    158167
    159168!Config  Key  = less1day
     
    600609       offline = .FALSE.
    601610       CALL getin('offline',offline)
     611     
     612!Config  Key  = type_trac
     613!Config  Desc = Choix de couplage avec model de chimie INCA ou REPROBUS
     614!Config  Def  = lmdz
     615!Config  Help =
     616!Config         'lmdz' = pas de couplage, pur LMDZ
     617!Config         'inca' = model de chime INCA
     618!Config         'repr' = model de chime REPROBUS
     619      type_trac = 'lmdz'
     620      CALL getin('type_trac',type_trac)
    602621
    603622!Config  Key  = config_inca
     
    677696      write(lunout,*)' tauyy = ', tauyy
    678697      write(lunout,*)' offline = ', offline
     698      write(lunout,*)' type_trac = ', type_trac
    679699      write(lunout,*)' config_inca = ', config_inca
    680700      write(lunout,*)' ok_dynzon = ', ok_dynzon
     
    795815       offline = .FALSE.
    796816       CALL getin('offline',offline)
     817
     818!Config  Key  = type_trac
     819!Config  Desc = Choix de couplage avec model de chimie INCA ou REPROBUS
     820!Config  Def  = lmdz
     821!Config  Help =
     822!Config         'lmdz' = pas de couplage, pur LMDZ
     823!Config         'inca' = model de chime INCA
     824!Config         'repr' = model de chime REPROBUS
     825      type_trac = 'lmdz'
     826      CALL getin('type_trac',type_trac)
    797827
    798828!Config  Key  = config_inca
     
    921951      write(lunout,*)' tauy = ', tauy
    922952      write(lunout,*)' offline = ', offline
     953      write(lunout,*)' type_trac = ', type_trac
    923954      write(lunout,*)' config_inca = ', config_inca
    924955      write(lunout,*)' ok_dynzon = ', ok_dynzon
  • trunk/LMDZ.COMMON/libf/dyn3d/control_mod.F90

    r270 r492  
    1010  IMPLICIT NONE
    1111
    12   REAL    :: periodav
     12  REAL    :: periodav, starttime
    1313  INTEGER :: nday,day_step,iperiod,iapp_tracvl,nsplit_phys
    1414  INTEGER :: iconser,iecri,dissip_period,iphysiq,iecrimoy
  • trunk/LMDZ.COMMON/libf/dyn3d/dynetat0.F

    r1 r492  
    119119      day_ini = tab_cntrl(30)
    120120      itau_dyn = tab_cntrl(31)
     121      start_time = tab_cntrl(32)
    121122c   .................................................................
    122123c
  • trunk/LMDZ.COMMON/libf/dyn3d/dynredem.F

    r6 r492  
    120120       tab_cntrl(30) = REAL(iday_end)
    121121       tab_cntrl(31) = REAL(itau_dyn + itaufin)
     122c start_time: start_time of simulation (not necessarily 0.)
     123       tab_cntrl(32) = start_time
    122124c
    123125c    .........................................................
     
    640642#endif
    641643
    642       IF (config_inca /= 'none') THEN
     644      IF (type_trac == 'inca') THEN
    643645! Ajout Anne pour lecture valeurs traceurs dans un fichier start_trac.nc
    644646         ierr_file = NF_OPEN ("start_trac.nc", NF_NOWRITE,nid_trac)
     
    653655      do iq=1,nqtot
    654656
    655          IF (config_inca == 'none') THEN
     657         IF (type_trac /= 'inca') THEN
    656658            ierr = NF_INQ_VARID(nid, tname(iq), nvarid)
    657659            IF (ierr .NE. NF_NOERR) THEN
     
    665667            ierr = NF_PUT_VAR_REAL (nid,nvarid,q(1,1,iq))
    666668#endif
    667         ELSE ! config_inca = 'chem' ou 'aero'
     669        ELSE ! type_trac = inca
    668670! lecture de la valeur du traceur dans start_trac.nc
    669671           IF (ierr_file .ne. 2) THEN
     
    729731#endif
    730732          ENDIF ! (ierr_file .ne. 2)
    731        END IF   ! config_inca
     733       END IF   !type_trac
    732734     
    733735      ENDDO
  • trunk/LMDZ.COMMON/libf/dyn3d/gcm.F

    r270 r492  
    223223c-----------------------------------------------------------------------
    224224
    225       IF (config_inca /= 'none') THEN
     225      IF (type_trac == 'inca') THEN
    226226#ifdef INCA
    227227      call init_const_lmdz(nbtr,anneeref,dayref,iphysiq,day_step,nday,
     
    277277      endif ! of if (read_start)
    278278
    279       IF (config_inca /= 'none') THEN
     279      IF (type_trac == 'inca') THEN
    280280#ifdef INCA
    281281         call init_inca_dim(klon,llm,iim,jjm,
     
    319319C on remet le calendrier à zero si demande
    320320c
     321      IF (start_time /= starttime) then
     322        WRITE(lunout,*)' GCM: Attention l''heure de depart lue dans le'
     323     &,' fichier restart ne correspond pas à celle lue dans le run.def'
     324        IF (raz_date == 1) then
     325          WRITE(lunout,*)'Je prends l''heure lue dans run.def'
     326          start_time = starttime
     327        ELSE
     328          WRITE(lunout,*)'Je m''arrete'
     329          CALL abort
     330        ENDIF
     331      ENDIF
    321332      IF (raz_date == 1) THEN
    322333        annee_ref = anneeref
  • trunk/LMDZ.COMMON/libf/dyn3d/infotrac.F90

    r66 r492  
    3232  SUBROUTINE infotrac_init
    3333    USE control_mod
     34#ifdef REPROBUS
     35    USE CHEM_REP, ONLY : Init_chem_rep_trac
     36#endif
    3437    IMPLICIT NONE
    3538!=======================================================================
     
    8588   
    8689    IF (planet_type=='earth') THEN
    87      IF (config_inca=='none') THEN
    88        type_trac='lmdz'
     90     ! Coherence test between parameter type_trac, config_inca and preprocessing keys
     91     IF (type_trac=='inca') THEN
     92       WRITE(lunout,*) 'You have choosen to couple with INCA chemestry model : type_trac=', &
     93            type_trac,' config_inca=',config_inca
     94       IF (config_inca/='aero' .AND. config_inca/='chem') THEN
     95          WRITE(lunout,*) 'Incoherence between type_trac and config_inca. Model stops. Modify run.def'
     96          CALL abort_gcm('infotrac_init','Incoherence between type_trac and config_inca',1)
     97       END IF
     98#ifndef INCA
     99       WRITE(lunout,*) 'To run this option you must add cpp key INCA and compile with INCA code'
     100       CALL abort_gcm('infotrac_init','You must compile with cpp key INCA',1)
     101#endif
     102     ELSE IF (type_trac=='repr') THEN
     103       WRITE(lunout,*) 'You have choosen to couple with REPROBUS chemestry model : type_trac=', type_trac
     104#ifndef REPROBUS
     105       WRITE(lunout,*) 'To run this option you must add cpp key REPROBUS and compile with REPRPBUS code'
     106       CALL abort_gcm('infotrac_init','You must compile with cpp key REPROBUS',1)
     107#endif
     108     ELSE IF (type_trac == 'lmdz') THEN
     109       WRITE(lunout,*) 'Tracers are treated in LMDZ only : type_trac=', type_trac
    89110     ELSE
    90        type_trac='inca'
     111       WRITE(lunout,*) 'type_trac=',type_trac,' not possible. Model stops'
     112       CALL abort_gcm('infotrac_init','bad parameter',1)
     113     END IF
     114
     115     ! Test if config_inca is other then none for run without INCA
     116     IF (type_trac/='inca' .AND. config_inca/='none') THEN
     117       WRITE(lunout,*) 'config_inca will now be changed to none as you do not couple with INCA model'
     118       config_inca='none'
    91119     END IF
    92120    ELSE
    93121     type_trac='plnt'  ! planets... May want to dissociate between each later.
    94     ENDIF
     122    ENDIF ! of IF (planet_type=='earth')
    95123
    96124!-----------------------------------------------------------------------
     
    101129!-----------------------------------------------------------------------
    102130    IF (planet_type=='earth') THEN
    103      IF (type_trac == 'lmdz') THEN
     131     IF (type_trac == 'lmdz' .OR. type_trac == 'repr') THEN
    104132       OPEN(90,file='traceur.def',form='formatted',status='old', iostat=ierr)
    105133       IF(ierr.EQ.0) THEN
    106           WRITE(lunout,*) 'Open traceur.def : ok'
     134          WRITE(lunout,*) trim(modname),': Open traceur.def : ok'
    107135          READ(90,*) nqtrue
    108136       ELSE
    109           WRITE(lunout,*) 'Problem in opening traceur.def'
    110           WRITE(lunout,*) 'ATTENTION using defaut values'
     137          WRITE(lunout,*) trim(modname),': Problem in opening traceur.def'
     138          WRITE(lunout,*) trim(modname),': WARNING using defaut values'
    111139          nqtrue=4 ! Defaut value
    112140       END IF
    113141       ! For Earth, water vapour & liquid tracers are not in the physics
    114142       nbtr=nqtrue-2
    115      ELSE
     143     ELSE ! type_trac=inca
    116144       ! nbtr has been read from INCA by init_cont_lmdz() in gcm.F
    117145       nqtrue=nbtr+2
     
    121149       WRITE(lunout,*) trim(modname),': nqtrue=',nqtrue, ' is not allowded. 2 tracers is the minimum'
    122150       CALL abort_gcm('infotrac_init','Not enough tracers',1)
     151     END IF
     152
     153! Transfert number of tracers to Reprobus
     154     IF (type_trac == 'repr') THEN
     155#ifdef REPROBUS
     156       CALL Init_chem_rep_trac(nbtr)
     157#endif
    123158     END IF
    124159
     
    173208!---------------------------------------------------------------------
    174209    IF (planet_type=='earth') THEN
    175      IF (type_trac == 'lmdz') THEN
     210     IF (type_trac == 'lmdz' .OR. type_trac == 'repr') THEN
    176211       IF(ierr.EQ.0) THEN
    177212          ! Continue to read tracer.def
  • trunk/LMDZ.COMMON/libf/dyn3d/iniacademic.F90

    r270 r492  
    209209        ! surface pressure
    210210        if (iflag_phys>2) then
    211            ps(:)=108080.  ! Earth aqua/terra planets
    212         else
     211           ! specific value for CMIP5 aqua/terra planets
     212           ! "Specify the initial dry mass to be equivalent to
     213           !  a global mean surface pressure (101325 minus 245) Pa."
     214           ps(:)=101080. 
     215        else
     216           ! use reference surface pressure
    213217           ps(:)=preff
    214218        endif
     219       
    215220        ! ground geopotential
    216221        phis(:)=0.
  • trunk/LMDZ.COMMON/libf/dyn3d/leapfrog.F

    r270 r492  
    270270   1  CONTINUE
    271271
    272       jD_cur = jD_ref + day_ini - day_ref + int (itau * dtvr / daysec)
    273       jH_cur = jH_ref +                                                 &
     272      jD_cur = jD_ref + day_ini - day_ref +                             &
     273     &          int (itau * dtvr / daysec)
     274      jH_cur = jH_ref + start_time +                                    &
    274275     &          (itau * dtvr / daysec - int(itau * dtvr / daysec))
     276      jD_cur = jD_cur + int(jH_cur)
     277      jH_cur = jH_cur - int(jH_cur)
    275278
    276279
     
    422425!           rdaym_ini  = itau * dtvr / daysec
    423426!           rdayvrai   = rdaym_ini  + day_ini
    424            jD_cur = jD_ref + day_ini - day_ref
    425      $        + int (itau * dtvr / daysec)
    426            jH_cur = jH_ref +                                            &
    427      &              (itau * dtvr / daysec - int(itau * dtvr / daysec))
     427           jD_cur = jD_ref + day_ini - day_ref +                        &
     428     &          int (itau * dtvr / daysec)
     429           jH_cur = jH_ref + start_time +                               &
     430     &          (itau * dtvr / daysec - int(itau * dtvr / daysec))
     431           jD_cur = jD_cur + int(jH_cur)
     432           jH_cur = jH_cur - int(jH_cur)
    428433!         write(lunout,*)'itau, jD_cur = ', itau, jD_cur, jH_cur
    429434!         call ju2ymds(jD_cur+jH_cur, an, mois, jour, secondes)
     
    727732                call abort_gcm(modname,abort_message,0)
    728733              else
    729                 CALL dynredem1("restart.nc",0.0,
     734                CALL dynredem1("restart.nc",start_time,
    730735     &                         vcov,ucov,teta,q,masse,ps)
    731736              endif ! of if (planet_type.eq."mars")
     
    847852                  call abort_gcm(modname,abort_message,0)
    848853                else
    849                   CALL dynredem1("restart.nc",0.0,
     854                  CALL dynredem1("restart.nc",start_time,
    850855     &                         vcov,ucov,teta,q,masse,ps)
    851856                endif ! of if (planet_type.eq."mars")
  • trunk/LMDZ.COMMON/libf/dyn3d/temps.h

    r1 r492  
    11!
    2 ! $Id: temps.h 1279 2009-12-10 09:02:56Z fairhead $
     2! $Id: temps.h 1577 2011-10-20 15:06:47Z fairhead $
    33!
    44!  ATTENTION!!!!: ce fichier include est compatible format fixe/format libre
     
    1414
    1515      COMMON/temps/itaufin, dt, day_ini, day_end, annee_ref, day_ref,   &
    16      &             itau_dyn, itau_phy, jD_ref, jH_ref, calend
     16     &             itau_dyn, itau_phy, jD_ref, jH_ref, calend,          &
     17     &             start_time
     18
    1719
    1820      INTEGER   itaufin
    1921      INTEGER itau_dyn, itau_phy
    2022      INTEGER day_ini, day_end, annee_ref, day_ref
    21       REAL      dt, jD_ref, jH_ref
     23      REAL      dt, jD_ref, jH_ref, start_time
    2224      CHARACTER (len=10) :: calend
    2325
  • trunk/LMDZ.COMMON/libf/dyn3dpar/ce0l.F90

    r270 r492  
    11!
    2 ! $Id: ce0l.F90 1511 2011-04-28 15:21:47Z jghattas $
     2! $Id: ce0l.F90 1600 2011-12-06 13:16:30Z jghattas $
    33!
    44!-------------------------------------------------------------------------------
     
    1919  USE dimphy
    2020  USE comgeomphy
     21  USE mod_phys_lmdz_para, mpi_root_xx=>mpi_root
     22  USE mod_const_mpi
    2123  USE infotrac
     24  USE parallel, ONLY: finalize_parallel
    2225
    2326#ifdef CPP_IOIPSL
     
    2831  IMPLICIT NONE
    2932#ifndef CPP_EARTH
    30   WRITE(lunout,*)'limit_netcdf: Earth-specific routine, needs Earth physics'
     33  WRITE(*,*)'limit_netcdf: Earth-specific routine, needs Earth physics'
    3134#else
    3235!-------------------------------------------------------------------------------
     
    3942#include "temps.h"
    4043#include "logic.h"
     44#ifdef CPP_MPI
     45      include 'mpif.h'
     46#endif
     47
    4148  INTEGER, PARAMETER            :: longcles=20
     49  INTEGER                       :: ierr
    4250  REAL,    DIMENSION(longcles)  :: clesphy0
    4351  REAL,    DIMENSION(iip1,jjp1) :: masque
     
    4755  CALL conf_gcm( 99, .TRUE. , clesphy0 )
    4856
     57#ifdef CPP_MPI
     58  CALL init_mpi
     59#endif
     60
    4961  CALL Init_Phys_lmdz(iim,jjp1,llm,1,(/(jjm-1)*iim+2/))
    5062  WRITE(lunout,*)'---> klon=',klon
     63  IF (mpi_size>1 .OR. omp_size>1) THEN
     64       CALL abort_gcm('ce0l','In parallel mode,                         &
     65 &                 ce0l must be called only                             &
     66 &                 for 1 process and 1 task',1)
     67  ENDIF
     68
    5169  CALL InitComgeomphy
    5270
     
    6785#endif
    6886
    69   IF (config_inca /= 'none') THEN
     87  IF (type_trac == 'inca') THEN
    7088#ifdef INCA
    71     CALL init_const_lmdz(nbtr,anneeref,dayref,iphysiq,day_step,nday)
    72     CALL init_inca_para(iim,jjm+1,klon,1,klon_mpi_para_nb,0)
    73     WRITE(lunout,*)'nbtr =' , nbtr
     89      CALL init_const_lmdz( &
     90         nbtr,anneeref,dayref,&
     91         iphysiq,day_step,nday,&
     92         nbsrf, is_oce,is_sic,&
     93         is_ter,is_lic)
     94     
    7495#endif
    7596  END IF
     
    100121     CALL grilles_gcm_netcdf_sub(masque,phis)
    101122  END IF
     123 
     124#ifdef CPP_MPI
     125!$OMP MASTER
     126  CALL MPI_FINALIZE(ierr)
     127  IF (ierr /= 0) CALL abort_gcm('ce0l','Error in MPI_FINALIZE',1)
     128!$OMP END MASTER
     129#endif
     130
    102131#endif
    103132! of #ifndef CPP_EARTH #else
  • trunk/LMDZ.COMMON/libf/dyn3dpar/conf_gcm.F

    r271 r492  
    1717      use parallel, ONLY : omp_chunk
    1818      USE control_mod
     19      USE infotrac, ONLY : type_trac
    1920      IMPLICIT NONE
    2021c-----------------------------------------------------------------------
     
    9798      CALL getin('lunout', lunout)
    9899      IF (lunout /= 5 .and. lunout /= 6) THEN
    99         OPEN(lunout,FILE='lmdz.out')
     100        OPEN(UNIT=lunout,FILE='lmdz.out_0000',ACTION='write',
     101     &          STATUS='unknown',FORM='formatted')
     102
    100103      ENDIF
    101104
     
    166169      nday = 10
    167170      CALL getin('nday',nday)
     171
     172!Config  Key  = starttime
     173!Config  Desc = Heure de depart de la simulation
     174!Config  Def  = 0
     175!Config  Help = Heure de depart de la simulation
     176!Config         en jour
     177      starttime = 0
     178      CALL getin('starttime',starttime)
    168179
    169180!Config  Key  = less1day
     
    623634       END IF
    624635       
     636!Config  Key  = type_trac
     637!Config  Desc = Choix de couplage avec model de chimie INCA ou REPROBUS
     638!Config  Def  = lmdz
     639!Config  Help =
     640!Config         'lmdz' = pas de couplage, pur LMDZ
     641!Config         'inca' = model de chime INCA
     642!Config         'repr' = model de chime REPROBUS
     643      type_trac = 'lmdz'
     644      CALL getin('type_trac',type_trac)
     645
    625646!Config  Key  = config_inca
    626647!Config  Desc = Choix de configuration de INCA
     
    699720      write(lunout,*)' tauyy = ', tauyy
    700721      write(lunout,*)' offline = ', offline
     722      write(lunout,*)' type_trac = ', type_trac
    701723      write(lunout,*)' config_inca = ', config_inca
    702724      write(lunout,*)' ok_dynzon = ', ok_dynzon
     
    825847     &         'only the file phystoke.nc will still be created '
    826848       END IF
     849
     850!Config  Key  = type_trac
     851!Config  Desc = Choix de couplage avec model de chimie INCA ou REPROBUS
     852!Config  Def  = lmdz
     853!Config  Help =
     854!Config         'lmdz' = pas de couplage, pur LMDZ
     855!Config         'inca' = model de chime INCA
     856!Config         'repr' = model de chime REPROBUS
     857      type_trac = 'lmdz'
     858      CALL getin('type_trac',type_trac)
    827859
    828860!Config  Key  = config_inca
     
    9741006      write(lunout,*)' tauy = ', tauy
    9751007      write(lunout,*)' offline = ', offline
     1008      write(lunout,*)' type_trac = ', type_trac
    9761009      write(lunout,*)' config_inca = ', config_inca
    9771010      write(lunout,*)' ok_dynzon = ', ok_dynzon
  • trunk/LMDZ.COMMON/libf/dyn3dpar/control_mod.F90

    r270 r492  
    1010  IMPLICIT NONE
    1111
    12   REAL    :: periodav
     12  REAL    :: periodav, starttime
    1313  INTEGER :: nday,day_step,iperiod,iapp_tracvl,nsplit_phys
    1414  INTEGER :: iconser,iecri,dissip_period,iphysiq,iecrimoy
  • trunk/LMDZ.COMMON/libf/dyn3dpar/dynetat0.F

    r1 r492  
    119119      day_ini = tab_cntrl(30)
    120120      itau_dyn = tab_cntrl(31)
     121      start_time = tab_cntrl(32)
    121122c   .................................................................
    122123c
  • trunk/LMDZ.COMMON/libf/dyn3dpar/dynredem.F

    r1 r492  
    120120       tab_cntrl(30) = REAL(iday_end)
    121121       tab_cntrl(31) = REAL(itau_dyn + itaufin)
     122c start_time: start_time of simulation (not necessarily 0.)
     123       tab_cntrl(32) = start_time
    122124c
    123125c    .........................................................
     
    136138c
    137139      ierr = NF_PUT_ATT_TEXT (nid, NF_GLOBAL, "title", 27,
    138      .                       "Fichier demmarage dynamique")
     140     .                       "Fichier demarrage dynamique")
    139141c
    140142c Definir les dimensions du fichiers:
     
    536538#include "iniprint.h"
    537539
    538 
    539540      INTEGER l
    540541      REAL vcov(ip1jm,llm),ucov(ip1jmp1,llm)
     
    641642#endif
    642643
    643       IF (config_inca /= 'none') THEN
     644      IF (type_trac == 'inca') THEN
    644645! Ajout Anne pour lecture valeurs traceurs dans un fichier start_trac.nc
    645646         ierr_file = NF_OPEN ("start_trac.nc", NF_NOWRITE,nid_trac)
     
    654655      do iq=1,nqtot
    655656
    656          IF (config_inca == 'none') THEN
     657         IF (type_trac /= 'inca') THEN
    657658            ierr = NF_INQ_VARID(nid, tname(iq), nvarid)
    658659            IF (ierr .NE. NF_NOERR) THEN
     
    666667            ierr = NF_PUT_VAR_REAL (nid,nvarid,q(1,1,iq))
    667668#endif
    668         ELSE ! config_inca = 'chem' ou 'aero'
     669        ELSE ! type_trac = inca
    669670! lecture de la valeur du traceur dans start_trac.nc
    670671           IF (ierr_file .ne. 2) THEN
     
    730731#endif
    731732          ENDIF ! (ierr_file .ne. 2)
    732        END IF   ! config_inca
     733       END IF   !type_trac
    733734     
    734735      ENDDO
  • trunk/LMDZ.COMMON/libf/dyn3dpar/dynredem_p.F

    r1 r492  
    11!
    2 ! $Id: dynredem_p.F 1403 2010-07-01 09:02:53Z fairhead $
     2! $Id: dynredem_p.F 1577 2011-10-20 15:06:47Z fairhead $
    33!
    44c
     
    120120       tab_cntrl(30) =  REAL(iday_end)
    121121       tab_cntrl(31) =  REAL(itau_dyn + itaufin)
     122c start_time: start_time of simulation (not necessarily 0.)
     123       tab_cntrl(32) = start_time
    122124c
    123125c    .........................................................
     
    650652#endif
    651653
    652       IF (config_inca /= 'none') THEN
     654      IF (type_trac == 'inca') THEN
    653655! Ajout Anne pour lecture valeurs traceurs dans un fichier start_trac.nc
    654656         inquire(FILE="start_trac.nc", EXIST=exist_file)
     
    667669      do iq=1,nqtot
    668670
    669          IF (config_inca == 'none') THEN
     671         IF (type_trac /= 'inca') THEN
    670672            ierr = NF_INQ_VARID(nid, tname(iq), nvarid)
    671673            IF (ierr .NE. NF_NOERR) THEN
     
    678680            ierr = NF_PUT_VAR_REAL (nid,nvarid,q(1,1,iq))
    679681#endif
    680         ELSE ! config_inca = 'chem' ou 'aero'
     682        ELSE ! type_trac = inca
    681683! lecture de la valeur du traceur dans start_trac.nc
    682684           IF (ierr_file .ne. 2) THEN
     
    732734#endif
    733735          ENDIF ! (ierr_file .ne. 2)
    734        END IF   ! config_inca
     736       END IF   ! type_trac
    735737     
    736738      ENDDO
  • trunk/LMDZ.COMMON/libf/dyn3dpar/filtreg_p.F

    r1 r492  
    208208               IF( ifiltre.EQ.-2 )   THEN
    209209                  DO j = jdfil,jffil
     210#ifdef BLAS
    210211                     CALL DGEMM("N", "N", iim, nbniv_loc, iim, 1.0,
    211212     &                    matrinvn(1,1,j), iim,
    212213     &                    champ_loc(1,j,1), iip1*nlat, 0.0,
    213214     &                    champ_fft(1,j-jdfil+1,1), iip1*nlat)
     215#else
     216                     champ_fft(:,j-jdfil+1,:)
     217     &                    =matmul(matrinvn(:,:,j),champ_loc(:iim,j,:))
     218#endif
    214219                  ENDDO
    215220                 
    216221               ELSE IF ( griscal )     THEN
    217222                  DO j = jdfil,jffil
     223#ifdef BLAS
    218224                     CALL DGEMM("N", "N", iim, nbniv_loc, iim, 1.0,
    219225     &                    matriceun(1,1,j), iim,
    220226     &                    champ_loc(1,j,1), iip1*nlat, 0.0,
    221227     &                    champ_fft(1,j-jdfil+1,1), iip1*nlat)
     228#else
     229                     champ_fft(:,j-jdfil+1,:)
     230     &                    =matmul(matriceun(:,:,j),champ_loc(:iim,j,:))
     231#endif
    222232                  ENDDO
    223233                 
    224234               ELSE
    225235                  DO j = jdfil,jffil
     236#ifdef BLAS
    226237                     CALL DGEMM("N", "N", iim, nbniv_loc, iim, 1.0,
    227238     &                    matricevn(1,1,j), iim,
    228239     &                    champ_loc(1,j,1), iip1*nlat, 0.0,
    229240     &                    champ_fft(1,j-jdfil+1,1), iip1*nlat)
     241#else
     242                     champ_fft(:,j-jdfil+1,:)
     243     &                    =matmul(matricevn(:,:,j),champ_loc(:iim,j,:))
     244#endif
    230245                  ENDDO
    231246                 
     
    236251               IF( ifiltre.EQ.-2 )   THEN
    237252                  DO j = jdfil,jffil
     253#ifdef BLAS
    238254                     CALL DGEMM("N", "N", iim, nbniv_loc, iim, 1.0,
    239255     &                    matrinvs(1,1,j-jfiltsu+1), iim,
    240256     &                    champ_loc(1,j,1), iip1*nlat, 0.0,
    241257     &                    champ_fft(1,j-jdfil+1,1), iip1*nlat)
     258#else
     259                     champ_fft(:,j-jdfil+1,:)
     260     &                    =matmul(matrinvs(:,:,j-jfiltsu+1),
     261     &                            champ_loc(:iim,j,:))
     262#endif
    242263                  ENDDO
    243264                 
     
    245266                 
    246267                  DO j = jdfil,jffil
     268#ifdef BLAS
    247269                     CALL DGEMM("N", "N", iim, nbniv_loc, iim, 1.0,
    248270     &                    matriceus(1,1,j-jfiltsu+1), iim,
    249271     &                    champ_loc(1,j,1), iip1*nlat, 0.0,
    250272     &                    champ_fft(1,j-jdfil+1,1), iip1*nlat)
     273#else
     274                     champ_fft(:,j-jdfil+1,:)
     275     &                    =matmul(matriceus(:,:,j-jfiltsu+1),
     276     &                            champ_loc(:iim,j,:))
     277#endif
    251278                  ENDDO
    252279                 
     
    254281                 
    255282                  DO j = jdfil,jffil
     283#ifdef BLAS
    256284                     CALL DGEMM("N", "N", iim, nbniv_loc, iim, 1.0,
    257285     &                    matricevs(1,1,j-jfiltsv+1), iim,
    258286     &                    champ_loc(1,j,1), iip1*nlat, 0.0,
    259287     &                    champ_fft(1,j-jdfil+1,1), iip1*nlat)
     288#else
     289                     champ_fft(:,j-jdfil+1,:)
     290     &                    =matmul(matricevs(:,:,j-jfiltsv+1),
     291     &                            champ_loc(:iim,j,:))
     292#endif
    260293                  ENDDO
    261294                 
  • trunk/LMDZ.COMMON/libf/dyn3dpar/gcm.F

    r130 r492  
    250250c-----------------------------------------------------------------------
    251251
    252       IF (config_inca /= 'none') THEN
     252      IF (type_trac == 'inca') THEN
    253253#ifdef INCA
    254254         call init_const_lmdz(
     
    337337C on remet le calendrier à zero si demande
    338338c
     339      IF (start_time /= starttime) then
     340        WRITE(lunout,*)' GCM: Attention l''heure de depart lue dans le'
     341     &,' fichier restart ne correspond pas à celle lue dans le run.def'
     342        IF (raz_date == 1) then
     343          WRITE(lunout,*)'Je prends l''heure lue dans run.def'
     344          start_time = starttime
     345        ELSE
     346          WRITE(lunout,*)'Je m''arrete'
     347          CALL abort
     348        ENDIF
     349      ENDIF
    339350      IF (raz_date == 1) THEN
    340351        annee_ref = anneeref
     
    480491c   Initialisation des dimensions d'INCA :
    481492c   --------------------------------------
    482       IF (config_inca /= 'none') THEN
     493      IF (type_trac == 'inca') THEN
    483494#ifdef INCA
    484495!$OMP PARALLEL
  • trunk/LMDZ.COMMON/libf/dyn3dpar/infotrac.F90

    r66 r492  
    3232  SUBROUTINE infotrac_init
    3333    USE control_mod
     34#ifdef REPROBUS
     35    USE CHEM_REP, ONLY : Init_chem_rep_trac
     36#endif
    3437    IMPLICIT NONE
    3538!=======================================================================
     
    8588   
    8689    IF (planet_type=='earth') THEN
    87      IF (config_inca=='none') THEN
    88        type_trac='lmdz'
     90     ! Coherence test between parameter type_trac, config_inca and preprocessing keys
     91     IF (type_trac=='inca') THEN
     92       WRITE(lunout,*) 'You have choosen to couple with INCA chemestry model : type_trac=', &
     93            type_trac,' config_inca=',config_inca
     94       IF (config_inca/='aero' .AND. config_inca/='chem') THEN
     95          WRITE(lunout,*) 'Incoherence between type_trac and config_inca. Model stops. Modify run.def'
     96          CALL abort_gcm('infotrac_init','Incoherence between type_trac and config_inca',1)
     97       END IF
     98#ifndef INCA
     99       WRITE(lunout,*) 'To run this option you must add cpp key INCA and compile with INCA code'
     100       CALL abort_gcm('infotrac_init','You must compile with cpp key INCA',1)
     101#endif
     102     ELSE IF (type_trac=='repr') THEN
     103       WRITE(lunout,*) 'You have choosen to couple with REPROBUS chemestry model : type_trac=', type_trac
     104#ifndef REPROBUS
     105       WRITE(lunout,*) 'To run this option you must add cpp key REPROBUS and compile with REPRPBUS code'
     106       CALL abort_gcm('infotrac_init','You must compile with cpp key REPROBUS',1)
     107#endif
     108     ELSE IF (type_trac == 'lmdz') THEN
     109       WRITE(lunout,*) 'Tracers are treated in LMDZ only : type_trac=', type_trac
    89110     ELSE
    90        type_trac='inca'
     111       WRITE(lunout,*) 'type_trac=',type_trac,' not possible. Model stops'
     112       CALL abort_gcm('infotrac_init','bad parameter',1)
     113     END IF
     114
     115     ! Test if config_inca is other then none for run without INCA
     116     IF (type_trac/='inca' .AND. config_inca/='none') THEN
     117       WRITE(lunout,*) 'config_inca will now be changed to none as you do not couple with INCA model'
     118       config_inca='none'
    91119     END IF
    92120    ELSE
    93121     type_trac='plnt'  ! planets... May want to dissociate between each later.
    94     ENDIF
     122    ENDIF ! of IF (planet_type=='earth')
    95123
    96124!-----------------------------------------------------------------------
     
    101129!-----------------------------------------------------------------------
    102130    IF (planet_type=='earth') THEN
    103      IF (type_trac == 'lmdz') THEN
     131     IF (type_trac == 'lmdz' .OR. type_trac == 'repr') THEN
    104132       OPEN(90,file='traceur.def',form='formatted',status='old', iostat=ierr)
    105133       IF(ierr.EQ.0) THEN
    106           WRITE(lunout,*) 'Open traceur.def : ok'
     134          WRITE(lunout,*) trim(modname),': Open traceur.def : ok'
    107135          READ(90,*) nqtrue
    108136       ELSE
    109           WRITE(lunout,*) 'Problem in opening traceur.def'
    110           WRITE(lunout,*) 'ATTENTION using defaut values'
     137          WRITE(lunout,*) trim(modname),': Problem in opening traceur.def'
     138          WRITE(lunout,*) trim(modname),': WARNING using defaut values'
    111139          nqtrue=4 ! Defaut value
    112140       END IF
    113141       ! For Earth, water vapour & liquid tracers are not in the physics
    114142       nbtr=nqtrue-2
    115      ELSE
     143     ELSE ! type_trac=inca
    116144       ! nbtr has been read from INCA by init_cont_lmdz() in gcm.F
    117145       nqtrue=nbtr+2
     
    121149       WRITE(lunout,*) trim(modname),': nqtrue=',nqtrue, ' is not allowded. 2 tracers is the minimum'
    122150       CALL abort_gcm('infotrac_init','Not enough tracers',1)
     151     END IF
     152
     153! Transfert number of tracers to Reprobus
     154     IF (type_trac == 'repr') THEN
     155#ifdef REPROBUS
     156       CALL Init_chem_rep_trac(nbtr)
     157#endif
    123158     END IF
    124159
     
    173208!---------------------------------------------------------------------
    174209    IF (planet_type=='earth') THEN
    175      IF (type_trac == 'lmdz') THEN
     210     IF (type_trac == 'lmdz' .OR. type_trac == 'repr') THEN
    176211       IF(ierr.EQ.0) THEN
    177212          ! Continue to read tracer.def
  • trunk/LMDZ.COMMON/libf/dyn3dpar/iniacademic.F90

    r270 r492  
    209209        ! surface pressure
    210210        if (iflag_phys>2) then
    211            ps(:)=108080.  ! Earth aqua/terra planets
    212         else
     211           ! specific value for CMIP5 aqua/terra planets
     212           ! "Specify the initial dry mass to be equivalent to
     213           !  a global mean surface pressure (101325 minus 245) Pa."
     214           ps(:)=101080. 
     215        else
     216           ! use reference surface pressure
    213217           ps(:)=preff
    214218        endif
     219       
    215220        ! ground geopotential
    216221        phis(:)=0.
  • trunk/LMDZ.COMMON/libf/dyn3dpar/leapfrog_p.F

    r270 r492  
    198198
    199199      INTEGER :: true_itau
    200       LOGICAL :: verbose=.true.
    201200      INTEGER :: iapptrac
    202201      INTEGER :: AdjustCount
     
    282281   1  CONTINUE
    283282
    284       jD_cur = jD_ref + day_ini - day_ref + int (itau * dtvr / daysec)
    285       jH_cur = jH_ref +                                                 &
     283      jD_cur = jD_ref + day_ini - day_ref +                             &
     284     &          int (itau * dtvr / daysec)
     285      jH_cur = jH_ref + start_time +                                    &
    286286     &          (itau * dtvr / daysec - int(itau * dtvr / daysec))
     287      if (jH_cur > 1.0 ) then
     288        jD_cur = jD_cur +1.
     289        jH_cur = jH_cur -1.
     290      endif
    287291
    288292
     
    441445           call allgather_timer_average
    442446
    443         if (Verbose) then
     447        if (prt_level > 9) then
    444448       
    445449        print *,'*********************************'
     
    761765           jD_cur = jD_ref + day_ini - day_ref
    762766     $        + int (itau * dtvr / daysec)
    763            jH_cur = jH_ref +                                            &
     767           jH_cur = jH_ref + start_time +                                &
    764768     &              (itau * dtvr / daysec - int(itau * dtvr / daysec))
    765769!         call ju2ymds(jD_cur+jH_cur, an, mois, jour, secondes)
     770           if (jH_cur > 1.0 ) then
     771             jD_cur = jD_cur +1.
     772             jH_cur = jH_cur -1.
     773           endif
    766774
    767775c rajout debug
  • trunk/LMDZ.COMMON/libf/dyn3dpar/parallel.F90

    r66 r492  
    11!
    2 ! $Id: parallel.F90 1487 2011-02-11 15:07:54Z jghattas $
     2! $Id: parallel.F90 1575 2011-09-21 13:57:48Z jghattas $
    33!
    44  module parallel
     
    4343      integer, dimension(3) :: blocklen,type
    4444      integer :: comp_id
    45 
     45      character(len=4)  :: num
     46      character(len=20) :: filename
     47 
    4648#ifdef CPP_OMP   
    4749      INTEGER :: OMP_GET_NUM_THREADS
     
    7577        mpi_rank=0
    7678      ENDIF
    77  
     79
     80
     81! Open text output file with mpi_rank in suffix of file name
     82      IF (lunout /= 5 .and. lunout /= 6) THEN
     83         WRITE(num,'(I4.4)') mpi_rank
     84         filename='lmdz.out_'//num
     85         IF (mpi_rank .NE. 0) THEN
     86            OPEN(UNIT=lunout,FILE=TRIM(filename),ACTION='write', &
     87               STATUS='unknown',FORM='formatted',IOSTAT=ierr)
     88         ENDIF
     89      ENDIF
     90
    7891     
    7992      allocate(jj_begin_para(0:mpi_size-1))
  • trunk/LMDZ.COMMON/libf/dyn3dpar/temps.h

    r1 r492  
    1414
    1515      COMMON/temps/itaufin, dt, day_ini, day_end, annee_ref, day_ref,   &
    16      &             itau_dyn, itau_phy, jD_ref, jH_ref, calend
     16     &             itau_dyn, itau_phy, jD_ref, jH_ref, calend,          &
     17     &             start_time
     18
    1719
    1820      INTEGER   itaufin
    1921      INTEGER itau_dyn, itau_phy
    2022      INTEGER day_ini, day_end, annee_ref, day_ref
    21       REAL      dt, jD_ref, jH_ref
     23      REAL      dt, jD_ref, jH_ref, start_time
    2224      CHARACTER (len=10) :: calend
    2325
  • trunk/LMDZ.COMMON/libf/filtrez/filtreg_mod.F90

    r1 r492  
     1!
     2! $Id $
     3!
    14MODULE filtreg_mod
    25
     
    4245    INTEGER ixmineq
    4346#endif
    44     EXTERNAL  inifgn
    4547    !
    4648    ! ------------------------------------------------------------
     
    7173    CALL inifgn(eignvl)
    7274    !
    73     PRINT *,' EIGNVL '
     75    PRINT *,'inifilr: EIGNVL '
    7476    PRINT 250,eignvl
    75 250 FORMAT( 1x,5e13.6)
     77250 FORMAT( 1x,5e14.6)
    7678    !
    7779    ! compute eigenvalues and eigenfunctions
     
    113115#endif
    114116    !
     117    ! For a regular grid, we want the filter to start at latitudes
     118    ! corresponding to lengths dx of the same size as dy (in terms
     119    ! of angles: dx=2*dy) => at colat0=0.5 (i.e. colatitude=30 degrees
     120    !  <=> latitude=60 degrees).
     121    ! Same idea for the zoomed grid: start filtering polewards as soon
     122    ! as length dx becomes of the same size as dy
    115123    !
    116124    colat0  =  MIN( 0.5, dymin/dxmin )
     
    158166    imx  = iim
    159167    !
    160     PRINT *,' TRUNCATION AT ',imx
    161     !
     168    PRINT *,'inifilr: TRUNCATION AT ',imx
     169    !
     170! Ehouarn: set up some defaults
     171    jfiltnu=2 ! avoid north pole
     172    jfiltsu=jjm ! avoid south pole (which is at jjm+1)
     173    jfiltnv=1 ! NB: no poles on the V grid
     174    jfiltsv=jjm
     175
    162176    DO j = 2, jjm/2+1
    163177       cof = COS( rlatu(j) )/ colat0
    164178       IF ( cof .LT. 1. ) THEN
    165           IF( rlamda(imx) * COS(rlatu(j) ).LT.1. ) jfiltnu= j
     179          IF( rlamda(imx) * COS(rlatu(j) ).LT.1. ) THEN
     180            jfiltnu= j
     181          ENDIF
    166182       ENDIF
    167183
    168184       cof = COS( rlatu(jjp1-j+1) )/ colat0
    169185       IF ( cof .LT. 1. ) THEN
    170           IF( rlamda(imx) * COS(rlatu(jjp1-j+1) ).LT.1. ) &
     186          IF( rlamda(imx) * COS(rlatu(jjp1-j+1) ).LT.1. ) THEN
    171187               jfiltsu= jjp1-j+1
     188          ENDIF
    172189       ENDIF
    173190    ENDDO
     
    176193       cof = COS( rlatv(j) )/ colat0
    177194       IF ( cof .LT. 1. ) THEN
    178           IF( rlamda(imx) * COS(rlatv(j) ).LT.1. ) jfiltnv= j
     195          IF( rlamda(imx) * COS(rlatv(j) ).LT.1. ) THEN
     196            jfiltnv= j
     197          ENDIF
    179198       ENDIF
    180199
    181200       cof = COS( rlatv(jjm-j+1) )/ colat0
    182201       IF ( cof .LT. 1. ) THEN
    183           IF( rlamda(imx) * COS(rlatv(jjm-j+1) ).LT.1. ) &
     202          IF( rlamda(imx) * COS(rlatv(jjm-j+1) ).LT.1. ) THEN
    184203               jfiltsv= jjm-j+1
     204          ENDIF
    185205       ENDIF
    186206    ENDDO
    187207    !                                 
    188208
    189     IF ( jfiltnu.LE.0 ) jfiltnu=1
    190209    IF( jfiltnu.GT. jjm/2 +1 )  THEN
    191210       PRINT *,' jfiltnu en dehors des valeurs acceptables ' ,jfiltnu
     
    193212    ENDIF
    194213
    195     IF( jfiltsu.LE.0) jfiltsu=1
    196214    IF( jfiltsu.GT.  jjm  +1 )  THEN
    197215       PRINT *,' jfiltsu en dehors des valeurs acceptables ' ,jfiltsu
     
    199217    ENDIF
    200218
    201     IF( jfiltnv.LE.0) jfiltnv=1
    202219    IF( jfiltnv.GT. jjm/2    )  THEN
    203220       PRINT *,' jfiltnv en dehors des valeurs acceptables ' ,jfiltnv
     
    205222    ENDIF
    206223
    207     IF( jfiltsv.LE.0) jfiltsv=1
    208224    IF( jfiltsv.GT.     jjm  )  THEN
    209225       PRINT *,' jfiltsv en dehors des valeurs acceptables ' ,jfiltsv
     
    211227    ENDIF
    212228
    213     PRINT *,' jfiltnv jfiltsv jfiltnu jfiltsu ' , &
     229    PRINT *,'inifilr: jfiltnv jfiltsv jfiltnu jfiltsu ' , &
    214230         jfiltnv,jfiltsv,jfiltnu,jfiltsu
    215231
    216232    IF(first_call_inifilr) THEN
    217233       ALLOCATE(matriceun(iim,iim,jfiltnu))
    218        ALLOCATE(matriceus(iim,iim,jfiltsu))
     234       ALLOCATE(matriceus(iim,iim,jjm-jfiltsu+1))
    219235       ALLOCATE(matricevn(iim,iim,jfiltnv))
    220        ALLOCATE(matricevs(iim,iim,jfiltsv))
     236       ALLOCATE(matricevs(iim,iim,jjm-jfiltsv+1))
    221237       ALLOCATE( matrinvn(iim,iim,jfiltnu))
    222        ALLOCATE( matrinvs(iim,iim,jfiltsu))
     238       ALLOCATE( matrinvs(iim,iim,jjm-jfiltsu+1))
    223239       first_call_inifilr = .FALSE.
    224240    ENDIF
     
    230246    !
    231247    DO j = 1,jjm
     248    !default initialization: all modes are retained (i.e. no filtering)
    232249       modfrstu( j ) = iim
    233250       modfrstv( j ) = iim
     
    306323
    307324    IF(jfiltnv.GE.jjm/2 .OR. jfiltnu.GE.jjm/2)THEN
    308 
     325! Ehouarn: and what are these for??? Trying to handle a limit case
     326!          where filters extend to and meet at the equator?
    309327       IF(jfiltnv.EQ.jfiltsv)jfiltsv=1+jfiltnv
    310328       IF(jfiltnu.EQ.jfiltsu)jfiltsu=1+jfiltnu
     
    334352             eignft(i,k) = eignfnv(k,i) * coff
    335353          ENDDO
    336        ENDDO
     354       ENDDO ! of DO i=1,iim
    337355#ifdef CRAY
    338356       CALL MXM( eignfnv,iim,eignft,iim,matriceun(1,1,j),iim )
     
    350368             ENDDO
    351369          ENDDO
    352        ENDDO
    353 #endif
    354 #endif
    355 
    356     ENDDO
     370       ENDDO ! of DO k = 1, iim
     371#endif
     372#endif
     373
     374    ENDDO ! of DO j = 2, jfiltnu
    357375
    358376    DO j = jfiltsu, jjm
     
    364382             eignft(i,k) = eignfnv(k,i) * coff
    365383          ENDDO
    366        ENDDO
     384       ENDDO ! of DO i=1,iim
    367385#ifdef CRAY
    368386       CALL MXM(eignfnv,iim,eignft,iim,matriceus(1,1,j-jfiltsu+1),iim)
     
    381399             ENDDO
    382400          ENDDO
    383        ENDDO
    384 #endif
    385 #endif
    386 
    387     ENDDO
     401       ENDDO ! of DO k = 1, iim
     402#endif
     403#endif
     404
     405    ENDDO ! of DO j = jfiltsu, jjm
    388406
    389407    !   ...................................................................
     
    421439#endif
    422440
    423     ENDDO
     441    ENDDO ! of DO j = 1, jfiltnv
    424442
    425443    DO j = jfiltsv, jjm
     
    452470#endif
    453471
    454     ENDDO
     472    ENDDO ! of DO j = jfiltsv, jjm
    455473
    456474    !   ...................................................................
     
    488506#endif
    489507
    490     ENDDO
     508    ENDDO ! of DO j = 2, jfiltnu
    491509
    492510    DO j = jfiltsu, jjm
     
    518536#endif
    519537
    520     ENDDO
     538    ENDDO ! of DO j = jfiltsu, jjm
    521539
    522540    IF (use_filtre_fft) THEN
  • trunk/LMDZ.COMMON/libf/grid/dimension/makdim

    r1 r492  
    1 for i in $* ; do
    2    list=$list.$i
     1#!/bin/bash
     2#set -xv
     3
     4# sanity check: do we have the required argument ?
     5if (( $# < 1 )) || (( $# > 3 ))
     6then
     7 echo "Wrong number of parameters in $0 !!!"
     8 echo " Usage:"
     9 echo "  $0 [im] [jm] lm"
     10 echo " where im, jm and lm are the dimensions"
     11 exit
     12fi
     13
     14# build "fichnom", the relevant 'dimensions.im.jm.lm' file name
     15for i in $*
     16  do
     17  list=$list.$i
    318done
    419fichdim=dimensions${list}
    520
    6 if [ ! -f $fichdim ] ; then
    7 # si le fichier de dimensions n'existe pas, on le cree
     21if [ ! -f $fichdim ]
     22    then
     23#    echo "$fichdim does not exist"
    824
    9   if [ $# -ge 3 ] ; then
    10      im=$1
    11      jm=$2
    12      lm=$3
    13      n2=$1
    14      ndm=1
     25    # assign values of im, jm and lm
     26    if [ $# -ge 3 ]
     27        then
     28        im=$1
     29        jm=$2
     30        lm=$3
     31        ndm=1
     32    elif [ $# -ge 2 ]
     33        then
     34        im=1
     35        jm=$1
     36        lm=$2
     37        ndm=1
     38    elif [ $# -ge 1 ]
     39        then
     40        im=1
     41        jm=1
     42        lm=$1
     43        ndm=1
     44    fi
    1545
    16 # Le test suivant est commente car il est inutile avec le nouveau
    17 # filtre filtrez. Attention avec le "vieux" filtre (F. Forget,11/1994)
    18 #
    19 #     while [ "$n2" -gt 2 ]; do
    20 #       n2=`expr $n2 / 2`
    21 #       ndm=`expr $ndm + 1`
    22 #       echo $n2
    23 #    done
    24 #    if [ "$n2" != 2 ] ; then
    25 #       echo le nombre de longitude doit etre une puissance de 2
    26 #       exit
    27 #    fi
    28 
    29 
    30   else if [ $# -ge 2 ] ; then
    31       im=1
    32       jm=$1
    33       lm=$2
    34       ndm=1
    35   else if [ $# -ge 1 ] ; then
    36       im=1
    37       jm=1
    38       lm=$1
    39       ndm=1
    40   else
    41          echo il faut au moins une dimension
    42          exit
    43   fi
    44 fi
    45 fi
    46 
     46# since the file doesn't exist, we create it
    4747cat << EOF > $fichdim
    4848!-----------------------------------------------------------------------
     
    6262fi
    6363
     64# remove 'old' dimensions.h file (if any) and replace it with new one
     65if [ -f ../dimensions.h ] ; then
    6466\rm ../dimensions.h
     67fi
    6568tar cf - $fichdim | ( cd .. ; tar xf - ; mv $fichdim dimensions.h )
     69# line above is a trick to preserve time of creation of dimensions.h files
Note: See TracChangeset for help on using the changeset viewer.