Changeset 1416 for trunk/LMDZ.GENERIC


Ignore:
Timestamp:
Apr 16, 2015, 10:23:36 AM (10 years ago)
Author:
milmd
Message:

Update newstart and start2archive programs to work with LMDZ.GENERIC or LMDZ.MARS dynamics. Modification of makegcm_ifort to compile on Ada.

Location:
trunk/LMDZ.GENERIC
Files:
6 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.GENERIC/libf/dyn3d/control_mod.F90

    r1216 r1416  
    1313  real,save :: periodav
    1414  integer,save :: ecritphy ! output data in "diagfi.nc" every ecritphy dynamical steps
     15  character(len=10),save :: planet_type ! planet type ('earth','mars',...)
     16  character(len=4),save :: config_inca
    1517
    1618end module control_mod
  • trunk/LMDZ.GENERIC/libf/dyn3d/dynetat0.F

    r1216 r1416  
    1       SUBROUTINE dynetat0(fichnom,nq,vcov,ucov,
     1      SUBROUTINE dynetat0(fichnom,vcov,ucov,
    22     .                    teta,q,masse,ps,phis,time)
    33      use infotrac, only: tname, nqtot
     
    3737
    3838      CHARACTER*(*) fichnom
    39       INTEGER nq
    4039      REAL vcov(ip1jm,llm),ucov(ip1jmp1,llm),teta(ip1jmp1,llm)
    41       REAL q(iip1,jjp1,llm,nq),masse(ip1jmp1,llm)
     40      REAL q(iip1,jjp1,llm,nqtot),masse(ip1jmp1,llm)
    4241      REAL ps(ip1jmp1),phis(ip1jmp1)
    4342
     
    318317
    319318
    320       IF(nq.GE.1) THEN
     319      IF(nqtot.GE.1) THEN
    321320        write(*,*) 'dynetat0: loading tracers'
    322          IF(nq.GT.99) THEN
     321         IF(nqtot.GT.99) THEN
    323322            PRINT*, "Trop de traceurs"
    324323            CALL abort
    325324         ENDIF
    326          nqold=nq
    327          DO iq=1,nq
     325         nqold=nqtot
     326         DO iq=1,nqtot
    328327!           str3(1:1)='q'
    329328!           WRITE(str3(2:3),'(i2.2)') iq
     
    352351           ENDIF
    353352         ENDDO
    354          if ((nqold.lt.nq).and.(nqold.ge.1)) then   
     353         if ((nqold.lt.nqtot).and.(nqold.ge.1)) then   
    355354c        case when new tracer are added in addition to old ones
    356355             write(*,*)'tracers 1 to ', nqold,'were already present'
     
    379378!              end do
    380379!            end if
    381          end if ! of if ((nqold.lt.nq).and.(nqold.ge.1))
    382       ENDIF ! of IF(nq.GE.1)
     380         end if ! of if ((nqold.lt.nqtot).and.(nqold.ge.1))
     381      ENDIF ! of IF(nqtot.GE.1)
    383382
    384383      ierr = NF_INQ_VARID (nid, "masse", nvarid)
  • trunk/LMDZ.GENERIC/libf/dyn3d/dynredem.F

    r1216 r1416  
    1       SUBROUTINE dynredem0(fichnom,idayref,anneeref,phis,nq)
    2       use infotrac, only: tname
     1      SUBROUTINE dynredem0(fichnom,idayref,phis)
     2      use infotrac, only: tname,nqtot
    33      IMPLICIT NONE
    44c=======================================================================
     
    2020c   Arguments:
    2121c   ----------
    22       INTEGER*4 idayref,anneeref
     22      INTEGER*4 idayref
    2323      REAL phis(ip1jmp1)
    2424      CHARACTER*(*) fichnom
    25       INTEGER nq
    2625
    2726c   Local:
     
    888887      dims4(3) = idim_llm
    889888      dims4(4) = idim_tim
    890       IF(nq.GE.1) THEN
    891          DO iq=1,nq
     889      IF(nqtot.GE.1) THEN
     890         DO iq=1,nqtot
    892891            IF (iq.GT.99) THEN
    893892               PRINT*, "Trop de traceurs"
     
    954953
    955954      SUBROUTINE dynredem1(fichnom,time,
    956      .                     vcov,ucov,teta,q,nq,masse,ps)
     955     .                     vcov,ucov,teta,q,masse,ps)
    957956      use infotrac, only: nqtot, tname
    958957      IMPLICIT NONE
     
    967966!#include"advtrac.h"
    968967
    969       INTEGER nq, l
     968      INTEGER l
    970969      REAL vcov(ip1jm,llm),ucov(ip1jmp1,llm)
    971970      REAL teta(ip1jmp1,llm)                   
     
    10451044#endif
    10461045
    1047       IF (nq.GT.99) THEN
     1046      IF (nqtot.GT.99) THEN
    10481047         PRINT*, "Trop de traceurs"
    10491048         CALL abort
    10501049      ENDIF
    1051       IF(nq.GE.1) THEN
    1052          DO iq=1,nq
     1050      IF(nqtot.GE.1) THEN
     1051         DO iq=1,nqtot
    10531052!            str3(1:1)='q'
    10541053!            WRITE(str3(2:3),'(i2.2)') iq
  • trunk/LMDZ.GENERIC/libf/dyn3d/gcm.F

    r1403 r1416  
    195195      allocate(dqfi(ip1jmp1,llm,nqtot))
    196196
    197       CALL dynetat0("start.nc",nqtot,vcov,ucov,
     197      CALL dynetat0("start.nc",vcov,ucov,
    198198     .              teta,q,masse,ps,phis, time_0)
    199199
     
    300300     . 'c''est a dire du jour',i7,3x,'au jour',i7//)
    301301
    302       CALL dynredem0("restart.nc",day_end,anne_ini,phis,nqtot)
     302      CALL dynredem0("restart.nc",day_end,phis)
    303303
    304304      ecripar = .TRUE.
     
    640640       CALL test_period ( ucov,vcov,teta,q,p,phis )
    641641       CALL dynredem1("restart.nc",0.0,
    642      .                     vcov,ucov,teta,q,nqtot,masse,ps)
     642     .                     vcov,ucov,teta,q,masse,ps)
    643643
    644644              CLOSE(99)
  • trunk/LMDZ.GENERIC/libf/dyn3d/infotrac.F90

    r1227 r1416  
    44! nqtot : total number of tracers and higher order of moment, water vapor and liquid included
    55  INTEGER, SAVE :: nqtot
    6   INTEGER,allocatable :: iadv(:)   ! tracer advection scheme number
    7   CHARACTER(len=20),allocatable ::  tname(:) ! tracer name
    8 
     6! CR: add number of tracers for water (for Earth model only!!)
     7  INTEGER, SAVE :: nqo
     8
     9! nbtr : number of tracers not including higher order of moment or water vapor or liquid
     10!        number of tracers used in the physics
     11  INTEGER, SAVE :: nbtr
     12
     13! Name variables
     14  CHARACTER(len=20), ALLOCATABLE, DIMENSION(:), SAVE :: tname ! tracer short name for restart and diagnostics
     15  CHARACTER(len=23), ALLOCATABLE, DIMENSION(:), SAVE :: ttext ! tracer long name for diagnostics
     16
     17! iadv  : index of trasport schema for each tracer
     18  INTEGER, ALLOCATABLE, DIMENSION(:), SAVE    :: iadv
     19
     20! niadv : vector keeping the coorspondance between all tracers(nqtot) treated in the
     21!         dynamic part of the code and the tracers (nbtr+2) used in the physics part of the code.
     22  INTEGER, ALLOCATABLE, DIMENSION(:), SAVE    :: niadv ! equivalent dyn / physique
     23
     24! conv_flg(it)=0 : convection desactivated for tracer number it
     25  INTEGER, ALLOCATABLE, DIMENSION(:), SAVE  :: conv_flg
     26! pbl_flg(it)=0  : boundary layer diffusion desactivaded for tracer number it
     27  INTEGER, ALLOCATABLE, DIMENSION(:), SAVE  :: pbl_flg
     28
     29  CHARACTER(len=4),SAVE :: type_trac
     30  CHARACTER(len=8),DIMENSION(:),ALLOCATABLE, SAVE :: solsym
     31 
    932CONTAINS
    1033
     34  SUBROUTINE infotrac_init
     35    USE control_mod
     36#ifdef REPROBUS
     37    USE CHEM_REP, ONLY : Init_chem_rep_trac
     38#endif
     39    IMPLICIT NONE
     40!=======================================================================
     41!
     42!   Auteur:  P. Le Van /L. Fairhead/F.Hourdin
     43!   -------
     44!   Modif special traceur F.Forget 05/94
     45!   Modif M-A Filiberti 02/02 lecture de traceur.def
     46!
     47!   Objet:
     48!   ------
     49!   GCM LMD nouvelle grille
     50!
     51!=======================================================================
     52!   ... modification de l'integration de q ( 26/04/94 ) ....
     53!-----------------------------------------------------------------------
     54! Declarations
     55
     56    INCLUDE "dimensions.h"
     57    INCLUDE "iniprint.h"
     58
     59! Local variables
     60    INTEGER, ALLOCATABLE, DIMENSION(:) :: hadv  ! index of horizontal trasport schema
     61    INTEGER, ALLOCATABLE, DIMENSION(:) :: vadv  ! index of vertical trasport schema
     62
     63    CHARACTER(len=15), ALLOCATABLE, DIMENSION(:) :: tnom_0  ! tracer short name
     64    CHARACTER(len=3), DIMENSION(30) :: descrq
     65    CHARACTER(len=1), DIMENSION(3)  :: txts
     66    CHARACTER(len=2), DIMENSION(9)  :: txtp
     67    CHARACTER(len=23)               :: str1,str2
     68 
     69    INTEGER :: nqtrue  ! number of tracers read from tracer.def, without higer order of moment
     70    INTEGER :: iq, new_iq, iiq, jq, ierr, ierr2, ierr3
     71   
     72    character(len=80) :: line ! to store a line of text
     73 
     74    character(len=*),parameter :: modname="infotrac_init"
     75!-----------------------------------------------------------------------
     76! Initialization :
     77!
     78    txts=(/'x','y','z'/)
     79    txtp=(/'x ','y ','z ','xx','xy','xz','yy','yz','zz'/)
     80
     81    descrq(14)='VLH'
     82    descrq(10)='VL1'
     83    descrq(11)='VLP'
     84    descrq(12)='FH1'
     85    descrq(13)='FH2'
     86    descrq(16)='PPM'
     87    descrq(17)='PPS'
     88    descrq(18)='PPP'
     89    descrq(20)='SLP'
     90    descrq(30)='PRA'
     91   
     92    IF (planet_type=='earth') THEN
     93     ! Coherence test between parameter type_trac, config_inca and preprocessing keys
     94     IF (type_trac=='inca') THEN
     95       WRITE(lunout,*) 'You have choosen to couple with INCA chemestry model : type_trac=', &
     96            type_trac,' config_inca=',config_inca
     97       IF (config_inca/='aero' .AND. config_inca/='aeNP' .AND. config_inca/='chem') THEN
     98          WRITE(lunout,*) 'Incoherence between type_trac and config_inca. Model stops. Modify run.def'
     99          CALL abort_gcm('infotrac_init','Incoherence between type_trac and config_inca',1)
     100       END IF
     101#ifndef INCA
     102       WRITE(lunout,*) 'To run this option you must add cpp key INCA and compile with INCA code'
     103       CALL abort_gcm('infotrac_init','You must compile with cpp key INCA',1)
     104#endif
     105     ELSE IF (type_trac=='repr') THEN
     106       WRITE(lunout,*) 'You have choosen to couple with REPROBUS chemestry model : type_trac=', type_trac
     107#ifndef REPROBUS
     108       WRITE(lunout,*) 'To run this option you must add cpp key REPROBUS and compile with REPRPBUS code'
     109       CALL abort_gcm('infotrac_init','You must compile with cpp key REPROBUS',1)
     110#endif
     111     ELSE IF (type_trac == 'lmdz') THEN
     112       WRITE(lunout,*) 'Tracers are treated in LMDZ only : type_trac=', type_trac
     113     ELSE
     114       WRITE(lunout,*) 'type_trac=',type_trac,' not possible. Model stops'
     115       CALL abort_gcm('infotrac_init','bad parameter',1)
     116     END IF
     117
     118     ! Test if config_inca is other then none for run without INCA
     119     IF (type_trac/='inca' .AND. config_inca/='none') THEN
     120       WRITE(lunout,*) 'config_inca will now be changed to none as you do not couple with INCA model'
     121       config_inca='none'
     122     END IF
     123    ELSE
     124     type_trac='plnt'  ! planets... May want to dissociate between each later.
     125    ENDIF ! of IF (planet_type=='earth')
     126
     127!-----------------------------------------------------------------------
     128!
     129! 1) Get the true number of tracers + water vapor/liquid
     130!    Here true tracers (nqtrue) means declared tracers (only first order)
     131!
     132!-----------------------------------------------------------------------
     133    IF (planet_type=='earth') THEN
     134     IF (type_trac == 'lmdz' .OR. type_trac == 'repr') THEN
     135       OPEN(90,file='traceur.def',form='formatted',status='old', iostat=ierr)
     136       IF(ierr.EQ.0) THEN
     137          WRITE(lunout,*) trim(modname),': Open traceur.def : ok'
     138          READ(90,*) nqtrue
     139       ELSE
     140          WRITE(lunout,*) trim(modname),': Problem in opening traceur.def'
     141          WRITE(lunout,*) trim(modname),': WARNING using defaut values'
     142          nqtrue=4 ! Defaut value
     143       END IF
     144       ! For Earth, water vapour & liquid tracers are not in the physics
     145       nbtr=nqtrue-2
     146     ELSE ! type_trac=inca
     147       ! nbtr has been read from INCA by init_cont_lmdz() in gcm.F
     148       nqtrue=nbtr+2
     149     END IF
     150
     151     IF (nqtrue < 2) THEN
     152       WRITE(lunout,*) trim(modname),': nqtrue=',nqtrue, ' is not allowded. 2 tracers is the minimum'
     153       CALL abort_gcm('infotrac_init','Not enough tracers',1)
     154     END IF
     155
     156! Transfert number of tracers to Reprobus
     157     IF (type_trac == 'repr') THEN
     158#ifdef REPROBUS
     159       CALL Init_chem_rep_trac(nbtr)
     160#endif
     161     END IF
     162
     163    ELSE  ! not Earth
     164       OPEN(90,file='traceur.def',form='formatted',status='old', iostat=ierr)
     165       IF(ierr.EQ.0) THEN
     166          WRITE(lunout,*) 'Open traceur.def : ok'
     167          READ(90,*) nqtrue
     168       ELSE
     169          WRITE(lunout,*) 'Problem in opening traceur.def'
     170          WRITE(lunout,*) 'ATTENTION using defaut values: nqtrue=1'
     171          nqtrue=1 ! Defaut value
     172       END IF
     173       ! Other planets (for now); we have the same number of tracers
     174       ! in the dynamics than in the physics
     175       nbtr=nqtrue
     176     
     177    ENDIF  ! planet_type
     178!
     179! Allocate variables depending on nqtrue and nbtr
     180!
     181    ALLOCATE(tnom_0(nqtrue), hadv(nqtrue), vadv(nqtrue))
     182    ALLOCATE(conv_flg(nbtr), pbl_flg(nbtr), solsym(nbtr))
     183    conv_flg(:) = 1 ! convection activated for all tracers
     184    pbl_flg(:)  = 1 ! boundary layer activated for all tracers
     185
     186!-----------------------------------------------------------------------
     187! 2)     Choix  des schemas d'advection pour l'eau et les traceurs
     188!
     189!     iadv = 1    schema  transport type "humidite specifique LMD"
     190!     iadv = 2    schema   amont
     191!     iadv = 14   schema  Van-leer + humidite specifique
     192!                            Modif F.Codron
     193!     iadv = 10   schema  Van-leer (retenu pour l'eau vapeur et liquide)
     194!     iadv = 11   schema  Van-Leer pour hadv et version PPM (Monotone) pour vadv
     195!     iadv = 12   schema  Frederic Hourdin I
     196!     iadv = 13   schema  Frederic Hourdin II
     197!     iadv = 16   schema  PPM Monotone(Collela & Woodward 1984)
     198!     iadv = 17   schema  PPM Semi Monotone (overshoots autorisés)
     199!     iadv = 18   schema  PPM Positif Defini (overshoots undershoots autorisés)
     200!     iadv = 20   schema  Slopes
     201!     iadv = 30   schema  Prather
     202!
     203!        Dans le tableau q(ij,l,iq) : iq = 1  pour l'eau vapeur
     204!                                     iq = 2  pour l'eau liquide
     205!       Et eventuellement             iq = 3,nqtot pour les autres traceurs
     206!
     207!        iadv(1): choix pour l'eau vap. et  iadv(2) : choix pour l'eau liq.
     208!------------------------------------------------------------------------
     209!
     210!    Get choice of advection schema from file tracer.def or from INCA
     211!---------------------------------------------------------------------
     212    IF (planet_type=='earth') THEN
     213     IF (type_trac == 'lmdz' .OR. type_trac == 'repr') THEN
     214       IF(ierr.EQ.0) THEN
     215          ! Continue to read tracer.def
     216          DO iq=1,nqtrue
     217             READ(90,*) hadv(iq),vadv(iq),tnom_0(iq)
     218          END DO
     219          CLOSE(90) 
     220       ELSE ! Without tracer.def, set default values (for Earth!)
     221         if ((nqtrue==4).and.(planet_type=="earth")) then
     222          hadv(1) = 14
     223          vadv(1) = 14
     224          tnom_0(1) = 'H2Ov'
     225          hadv(2) = 10
     226          vadv(2) = 10
     227          tnom_0(2) = 'H2Ol'
     228          hadv(3) = 10
     229          vadv(3) = 10
     230          tnom_0(3) = 'RN'
     231          hadv(4) = 10
     232          vadv(4) = 10
     233          tnom_0(4) = 'PB'
     234         else
     235           ! Error message, we need a traceur.def file
     236           write(lunout,*) trim(modname),&
     237           ': Cannot set default tracer names!'
     238           write(lunout,*) trim(modname),' Make a traceur.def file!!!'
     239           CALL abort_gcm('infotrac_init','Need a traceur.def file!',1)
     240         endif ! of if (nqtrue==4)
     241       END IF
     242       
     243!CR: nombre de traceurs de l eau
     244       if (tnom_0(3) == 'H2Oi') then
     245          nqo=3
     246       else
     247          nqo=2
     248       endif
     249
     250       WRITE(lunout,*) trim(modname),': Valeur de traceur.def :'
     251       WRITE(lunout,*) trim(modname),': nombre de traceurs ',nqtrue
     252       DO iq=1,nqtrue
     253          WRITE(lunout,*) hadv(iq),vadv(iq),tnom_0(iq)
     254       END DO
     255
     256     ELSE  ! type_trac=inca : config_inca='aero' ou 'chem'
     257! le module de chimie fournit les noms des traceurs
     258! et les schemas d'advection associes.
     259     
     260#ifdef INCA
     261       CALL init_transport( &
     262            hadv, &
     263            vadv, &
     264            conv_flg, &
     265            pbl_flg,  &
     266            tracnam)
     267#endif
     268       tnom_0(1)='H2Ov'
     269       tnom_0(2)='H2Ol'
     270
     271       DO iq =3,nqtrue
     272          tnom_0(iq)=solsym(iq-2)
     273       END DO
     274       nqo = 2
     275
     276     END IF ! type_trac
     277
     278    ELSE  ! not Earth
     279       IF(ierr.EQ.0) THEN
     280          ! Continue to read tracer.def
     281          DO iq=1,nqtrue
     282             !READ(90,*) hadv(iq),vadv(iq),tnom_0(iq)
     283            ! try to be smart when reading traceur.def
     284            read(90,'(80a)') line ! store the line from traceur.def
     285            ! assume format is hadv,vadv,tnom_0
     286            read(line,*,iostat=ierr2) hadv(iq),vadv(iq),tnom_0(iq)
     287            if (ierr2.ne.0) then
     288              ! maybe format is tnom0,hadv,vadv
     289              read(line,*,iostat=ierr3) tnom_0(iq),hadv(iq),vadv(iq)
     290              if (ierr3.ne.0) then
     291                ! assume only tnom0 is provided (havd and vad default to 10)
     292                read(line,*) tnom_0(iq)
     293                hadv(iq)=10
     294                vadv(iq)=10
     295              endif
     296            endif ! of if(ierr2.ne.0)
     297          END DO ! of DO iq=1,nqtrue
     298          CLOSE(90) 
     299       ELSE ! Without tracer.def
     300          hadv(1) = 10
     301          vadv(1) = 10
     302          tnom_0(1) = 'dummy'
     303       END IF
     304       
     305       WRITE(lunout,*) trim(modname),': Valeur de traceur.def :'
     306       WRITE(lunout,*) trim(modname),': nombre de traceurs ',nqtrue
     307       DO iq=1,nqtrue
     308          WRITE(lunout,*) hadv(iq),vadv(iq),tnom_0(iq)
     309       END DO
     310
     311    ENDIF  ! planet_type
     312
     313!-----------------------------------------------------------------------
     314!
     315! 3) Verify if advection schema 20 or 30 choosen
     316!    Calculate total number of tracers needed: nqtot
     317!    Allocate variables depending on total number of tracers
     318!-----------------------------------------------------------------------
     319    new_iq=0
     320    DO iq=1,nqtrue
     321       ! Add tracers for certain advection schema
     322       IF (hadv(iq)<20 .AND. vadv(iq)<20 ) THEN
     323          new_iq=new_iq+1  ! no tracers added
     324       ELSE IF (hadv(iq)==20 .AND. vadv(iq)==20 ) THEN
     325          new_iq=new_iq+4  ! 3 tracers added
     326       ELSE IF (hadv(iq)==30 .AND. vadv(iq)==30 ) THEN
     327          new_iq=new_iq+10 ! 9 tracers added
     328       ELSE
     329          WRITE(lunout,*) trim(modname),': This choice of advection schema is not available',iq,hadv(iq),vadv(iq)
     330          CALL abort_gcm('infotrac_init','Bad choice of advection schema - 1',1)
     331       END IF
     332    END DO
     333   
     334    IF (new_iq /= nqtrue) THEN
     335       ! The choice of advection schema imposes more tracers
     336       ! Assigne total number of tracers
     337       nqtot = new_iq
     338
     339       WRITE(lunout,*) trim(modname),': The choice of advection schema for one or more tracers'
     340       WRITE(lunout,*) 'makes it necessary to add tracers'
     341       WRITE(lunout,*) trim(modname)//': ',nqtrue,' is the number of true tracers'
     342       WRITE(lunout,*) trim(modname)//': ',nqtot, ' is the total number of tracers needed'
     343
     344    ELSE
     345       ! The true number of tracers is also the total number
     346       nqtot = nqtrue
     347    END IF
     348
     349!
     350! Allocate variables with total number of tracers, nqtot
     351!
     352    ALLOCATE(tname(nqtot), ttext(nqtot))
     353    ALLOCATE(iadv(nqtot), niadv(nqtot))
     354
     355!-----------------------------------------------------------------------
     356!
     357! 4) Determine iadv, long and short name
     358!
     359!-----------------------------------------------------------------------
     360    new_iq=0
     361    DO iq=1,nqtrue
     362       new_iq=new_iq+1
     363
     364       ! Verify choice of advection schema
     365       IF (hadv(iq)==vadv(iq)) THEN
     366          iadv(new_iq)=hadv(iq)
     367       ELSE IF (hadv(iq)==10 .AND. vadv(iq)==16) THEN
     368          iadv(new_iq)=11
     369       ELSE
     370          WRITE(lunout,*)trim(modname),': This choice of advection schema is not available',iq,hadv(iq),vadv(iq)
     371
     372          CALL abort_gcm('infotrac_init','Bad choice of advection schema - 2',1)
     373       END IF
     374     
     375       str1=tnom_0(iq)
     376       tname(new_iq)= tnom_0(iq)
     377       IF (iadv(new_iq)==0) THEN
     378          ttext(new_iq)=trim(str1)
     379       ELSE
     380          ttext(new_iq)=trim(tnom_0(iq))//descrq(iadv(new_iq))
     381       END IF
     382
     383       ! schemas tenant compte des moments d'ordre superieur
     384       str2=ttext(new_iq)
     385       IF (iadv(new_iq)==20) THEN
     386          DO jq=1,3
     387             new_iq=new_iq+1
     388             iadv(new_iq)=-20
     389             ttext(new_iq)=trim(str2)//txts(jq)
     390             tname(new_iq)=trim(str1)//txts(jq)
     391          END DO
     392       ELSE IF (iadv(new_iq)==30) THEN
     393          DO jq=1,9
     394             new_iq=new_iq+1
     395             iadv(new_iq)=-30
     396             ttext(new_iq)=trim(str2)//txtp(jq)
     397             tname(new_iq)=trim(str1)//txtp(jq)
     398          END DO
     399       END IF
     400    END DO
     401
     402!
     403! Find vector keeping the correspodence between true and total tracers
     404!
     405    niadv(:)=0
     406    iiq=0
     407    DO iq=1,nqtot
     408       IF(iadv(iq).GE.0) THEN
     409          ! True tracer
     410          iiq=iiq+1
     411          niadv(iiq)=iq
     412       ENDIF
     413    END DO
     414
     415
     416    WRITE(lunout,*) trim(modname),': Information stored in infotrac :'
     417    WRITE(lunout,*) trim(modname),': iadv  niadv tname  ttext :'
     418    DO iq=1,nqtot
     419       WRITE(lunout,*) iadv(iq),niadv(iq),&
     420       ' ',trim(tname(iq)),' ',trim(ttext(iq))
     421    END DO
     422
     423!
     424! Test for advection schema.
     425! This version of LMDZ only garantees iadv=10 and iadv=14 (14 only for water vapour) .
     426!
     427    DO iq=1,nqtot
     428       IF (iadv(iq)/=10 .AND. iadv(iq)/=14 .AND. iadv(iq)/=0) THEN
     429          WRITE(lunout,*)trim(modname),' STOP : The option iadv=',iadv(iq),' is not tested in this version of LMDZ'
     430          CALL abort_gcm('infotrac_init','In this version only iadv=10 and iadv=14 is tested!',1)
     431       ELSE IF (iadv(iq)==14 .AND. iq/=1) THEN
     432          WRITE(lunout,*)trim(modname),'STOP : The option iadv=',iadv(iq),' is not tested in this version of LMDZ'
     433          CALL abort_gcm('infotrac_init','In this version iadv=14 is only permitted for water vapour!',1)
     434       END IF
     435    END DO
     436
     437!-----------------------------------------------------------------------
     438! Finalize :
     439!
     440    DEALLOCATE(tnom_0, hadv, vadv)
     441
     442
     443  END SUBROUTINE infotrac_init
     444
     445! Ehouarn: routine iniadvtrac => from Mars/generic; does essentially the
     446!          same job as infotrac_init. To clean up and merge at some point...
    11447      subroutine iniadvtrac(nq,numvanle)
    12448!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     
    133569      end subroutine iniadvtrac
    134570
     571
    135572END MODULE infotrac
  • trunk/LMDZ.GENERIC/makegcm_ifort

    r1403 r1416  
    3939    setenv NCDFLIB /opt/netcdf/ifort/lib
    4040    setenv NCDFINC /opt/netcdf/ifort/include
     41else if ( `hostname` == ada337 || `hostname` == ada338 ) then
     42    echo "ADA cluster"
     43    setenv NCDFLIB /smplocal/pub/NetCDF/4.1.3/seq/lib
     44    setenv NCDFINC /smplocal/pub/NetCDF/4.1.3/seq/include
    4145else
    4246   # NetCDF, on LMD farm:
     
    651655        echo "Remaking the makefile!"
    652656        echo "src_dirs: $src_dirs"
    653         create_make_gcm $src_dirs >! tmp
     657        ./create_make_gcm $src_dirs >! tmp
    654658        \mv tmp makefile
    655659        echo "New makefile created."
Note: See TracChangeset for help on using the changeset viewer.