Changeset 1415 for trunk/LMDZ.MARS/libf


Ignore:
Timestamp:
Apr 14, 2015, 9:46:47 AM (10 years ago)
Author:
milmd
Message:

Update newstart and start2archive programs of LMDZ.GENERIC and LMDZ.MARS to the new organization.

Location:
trunk/LMDZ.MARS/libf
Files:
4 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.MARS/libf/dyn3d/defrun_new.F

    r1399 r1415  
    11      SUBROUTINE defrun_new( tapedef, etatinit )
     2#ifndef CPP_PARA
    23c
    34c-----------------------------------------------------------------------
     
    576577     &in run.def for this version... -> STOP ! '     
    577578      end if
    578 
    579       RETURN
     579#else
     580      write(*,*) "defrun_new should not be used in parallel mode!"
     581      stop
     582#endif
     583! of #ifndef CPP_PARA
    580584      END
  • trunk/LMDZ.MARS/libf/dynlonlat_phylonlat/phymars/datareadnc.F

    r1403 r1415  
    235235     .         iim, jjp1, rlonv, rlatu, zmea,zstd,zsig,zgam,zthe)
    236236
    237           CALL dump2d(iip1,jjp1,zmea,'zmea')
    238           CALL dump2d(iip1,jjp1,zstd,'zstd')
    239           CALL dump2d(iip1,jjp1,zsig,'zsig')
    240           CALL dump2d(iip1,jjp1,zgam,'zgam')
    241           CALL dump2d(iip1,jjp1,zthe,'zthe')
    242 
    243237      endif
    244238
     
    274268         z0(1:iimp1*jjp1)=pfield(1:iimp1*jjp1)*.01
    275269         ! multiplied by 0.01 to have z0 in m
    276          CALL dump2d(iimp1,jjp1,z0,'z0 in m')
    277270      elseif (k.eq.1) then                    ! albedo
    278271         do i=1,iimp1*jjp1
     
    300293
    301294      phisinit(1:iimp1*jjp1)=1000.*phisinit(1:iimp1*jjp1)
    302       CALL dump2d(iimp1,jjp1,phisinit,'Altitude in m')
    303295      phisinit(:)=g*phisinit(:)
    304296
  • trunk/LMDZ.MARS/libf/dynlonlat_phylonlat/phymars/newstart.F

    r1403 r1415  
    1616
    1717      use ioipsl_getincom, only: getin
    18       use infotrac, only: iniadvtrac, nqtot, tname
     18      use infotrac, only: infotrac_init, nqtot, tname
    1919      use tracer_mod, only: noms, mmol,
    2020     &                      igcm_dust_number, igcm_dust_mass,
     
    2626     &                     co2ice, emis
    2727      use comsoil_h, only: inertiedat, layer, mlayer, nsoilmx, tsoil
    28       use control_mod, only: day_step, iphysiq, anneeref
     28      use control_mod, only: day_step, iphysiq, anneeref, planet_type
    2929      use phyredem, only: physdem0, physdem1
    3030      use iostart, only: open_startphy
     
    179179      preff  = 610.    ! for Mars, instead of 101325. (Earth)
    180180      pa= 20           ! for Mars, instead of 500 (Earth)
     181      planet_type="mars"
    181182
    182183! initialize "serial/parallel" related stuff
     
    185186
    186187! Load tracer number and names:
    187       call iniadvtrac(nqtot,numvanle)
     188!      call iniadvtrac(nqtot,numvanle)
     189      call infotrac_init
    188190! allocate arrays
    189191      allocate(q(iip1,jjp1,llm,nqtot))
     
    16281630      phis(iip1,:) = phis(1,:)
    16291631
    1630       CALL inidissip ( lstardis, nitergdiv, nitergrot, niterh,
    1631      *                tetagdiv, tetagrot , tetatemp  )
     1632c      CALL inidissip ( lstardis, nitergdiv, nitergrot, niterh,
     1633c     *                tetagdiv, tetagrot , tetatemp  )
    16321634      itau=0
    16331635      if (choix_1.eq.0) then
     
    16441646c    $    phi,conser,du,dv,dteta,dp,w, pbaru,pbarv, day_ini )
    16451647
    1646       CALL dynredem0("restart.nc",day_ini,anneeref,phis,nqtot)
     1648      CALL dynredem0("restart.nc",day_ini,phis)
    16471649      CALL dynredem1("restart.nc",hour_ini,vcov,ucov,teta,q,
    1648      .               nqtot,masse,ps)
     1650     .               masse,ps)
    16491651C
    16501652C Ecriture etat initial physique
  • trunk/LMDZ.MARS/libf/dynlonlat_phylonlat/phymars/start2archive.F

    r1403 r1415  
    1919c=======================================================================
    2020
    21       use infotrac, only: iniadvtrac, nqtot, tname
     21      use infotrac, only: infotrac_init, nqtot, tname
    2222      use comsoil_h, only: nsoilmx, inertiedat
    2323      use surfdat_h, only: ini_surfdat_h, qsurf
     
    2525      use comgeomphy, only: initcomgeomphy
    2626      use filtreg_mod, only: inifilr
     27      use control_mod, only: planet_type
    2728      implicit none
    2829
     
    120121      CALL init_phys_lmdz(iim,jjp1,llm,1,(/(jjm-1)*iim+2/))
    121122      call initcomgeomphy
     123      planet_type='mars'
    122124
    123125c=======================================================================
     
    125127c=======================================================================
    126128! Load tracer number and names:
    127       call iniadvtrac(nqtot,numvanle)
     129!      call iniadvtrac(nqtot,numvanle)
     130      call infotrac_init
    128131
    129132! allocate arrays:
     
    135138
    136139      fichnom = 'start.nc'
    137       CALL dynetat0(fichnom,nqtot,vcov,ucov,teta,q,masse,
     140      CALL dynetat0(fichnom,vcov,ucov,teta,q,masse,
    138141     .       ps,phis,timedyn)
    139142
Note: See TracChangeset for help on using the changeset viewer.