Ignore:
Timestamp:
Oct 27, 2012, 4:23:07 PM (12 years ago)
Author:
Laurent Fairhead
Message:

Fin du phasage de la dynamique parallele localisee (petite memoire) avec le tronc LMDZ5 r1671
Il reste quelques routines a verifier (en particulier ce qui touche a l'etude des cas academiques)
et la validation a effectuer


End of the phasing of the localised (low memory) parallel dynamics package with the
LMDZ5 trunk (r1671)
Some routines still need some checking (in particular the academic cases) and some
validation is still required

File:
1 edited

Legend:

Unmodified
Added
Removed
  • LMDZ5/trunk/libf/dyn3dmem/infotrac.F90

    r1632 r1673  
    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!=======================================================================
     
    6164    CHARACTER(len=1), DIMENSION(3)  :: txts
    6265    CHARACTER(len=2), DIMENSION(9)  :: txtp
    63     CHARACTER(len=13)               :: str1,str2
     66    CHARACTER(len=23)               :: str1,str2
    6467 
    6568    INTEGER :: nqtrue  ! number of tracers read from tracer.def, without higer order of moment
    6669    INTEGER :: iq, new_iq, iiq, jq, ierr
    67     INTEGER, EXTERNAL :: lnblnk
    68  
     70
     71    character(len=*),parameter :: modname="infotrac_init"
    6972!-----------------------------------------------------------------------
    7073! Initialization :
     
    8588   
    8689
    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'
    91     END IF
     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
     116    ! Test if config_inca is other then none for run without INCA
     117    IF (type_trac/='inca' .AND. config_inca/='none') THEN
     118       WRITE(lunout,*) 'config_inca will now be changed to none as you do not couple with INCA model'
     119       config_inca='none'
     120    END IF
     121
    92122
    93123!-----------------------------------------------------------------------
     
    97127!
    98128!-----------------------------------------------------------------------
    99     IF (type_trac == 'lmdz') THEN
     129    IF (type_trac == 'lmdz' .OR. type_trac == 'repr') THEN
    100130       OPEN(90,file='traceur.def',form='formatted',status='old', iostat=ierr)
    101131       IF(ierr.EQ.0) THEN
    102           WRITE(lunout,*) 'Open traceur.def : ok'
     132          WRITE(lunout,*) trim(modname),': Open traceur.def : ok'
    103133          READ(90,*) nqtrue
    104134       ELSE
    105           WRITE(lunout,*) 'Problem in opening traceur.def'
    106           WRITE(lunout,*) 'ATTENTION using defaut values'
    107           nqtrue=4 ! Defaut value
    108        END IF
    109        ! Attention! Only for planet_type=='earth'
    110        nbtr=nqtrue-2
    111     ELSE
    112        ! nbtr has been read from INCA by init_cont_lmdz() in gcm.F
     135          WRITE(lunout,*) trim(modname),': Problem in opening traceur.def'
     136          WRITE(lunout,*) trim(modname),': WARNING using defaut values'
     137          if (planet_type=='earth') then
     138            nqtrue=4 ! Default value for Earth
     139          else
     140            nqtrue=1 ! Default value for other planets
     141          endif
     142       END IF
     143       if ( planet_type=='earth') then
     144         ! For Earth, water vapour & liquid tracers are not in the physics
     145         nbtr=nqtrue-2
     146       else
     147         ! Other planets (for now); we have the same number of tracers
     148         ! in the dynamics than in the physics
     149         nbtr=nqtrue
     150       endif
     151    ELSE ! type_trac=inca
     152       ! nbtr has been read from INCA by init_const_lmdz() in gcm.F
    113153       nqtrue=nbtr+2
    114154    END IF
    115155
    116     IF (nqtrue < 2) THEN
    117        WRITE(lunout,*) 'nqtrue=',nqtrue, ' is not allowded. 2 tracers is the minimum'
     156    IF ((planet_type=="earth").and.(nqtrue < 2)) THEN
     157       WRITE(lunout,*) trim(modname),': nqtrue=',nqtrue, ' is not allowded. 2 tracers is the minimum'
    118158       CALL abort_gcm('infotrac_init','Not enough tracers',1)
    119159    END IF
     160   
     161! Transfert number of tracers to Reprobus
     162    IF (type_trac == 'repr') THEN
     163#ifdef REPROBUS
     164       CALL Init_chem_rep_trac(nbtr)
     165#endif
     166    END IF
     167       
    120168!
    121169! Allocate variables depending on nqtrue and nbtr
     
    152200!    Get choice of advection schema from file tracer.def or from INCA
    153201!---------------------------------------------------------------------
    154     IF (type_trac == 'lmdz') THEN
     202    IF (type_trac == 'lmdz' .OR. type_trac == 'repr') THEN
    155203       IF(ierr.EQ.0) THEN
    156204          ! Continue to read tracer.def
    157205          DO iq=1,nqtrue
    158              READ(90,999) hadv(iq),vadv(iq),tnom_0(iq)
     206             READ(90,*) hadv(iq),vadv(iq),tnom_0(iq)
    159207          END DO
    160208          CLOSE(90) 
    161        ELSE ! Without tracer.def
     209       ELSE ! Without tracer.def, set default values
     210         if (planet_type=="earth") then
     211          ! for Earth, default is to have 4 tracers
    162212          hadv(1) = 14
    163213          vadv(1) = 14
     
    172222          vadv(4) = 10
    173223          tnom_0(4) = 'PB'
     224         else ! default for other planets
     225          hadv(1) = 10
     226          vadv(1) = 10
     227          tnom_0(1) = 'dummy'
     228         endif ! of if (planet_type=="earth")
    174229       END IF
    175230       
    176        WRITE(lunout,*) 'Valeur de traceur.def :'
    177        WRITE(lunout,*) 'nombre de traceurs ',nqtrue
     231       WRITE(lunout,*) trim(modname),': Valeur de traceur.def :'
     232       WRITE(lunout,*) trim(modname),': nombre de traceurs ',nqtrue
    178233       DO iq=1,nqtrue
    179234          WRITE(lunout,*) hadv(iq),vadv(iq),tnom_0(iq)
     
    217272          new_iq=new_iq+10 ! 9 tracers added
    218273       ELSE
    219           WRITE(lunout,*) 'This choice of advection schema is not available'
     274          WRITE(lunout,*) trim(modname),': This choice of advection schema is not available',iq,hadv(iq),vadv(iq)
    220275          CALL abort_gcm('infotrac_init','Bad choice of advection schema - 1',1)
    221276       END IF
     
    227282       nqtot = new_iq
    228283
    229        WRITE(lunout,*) 'The choice of advection schema for one or more tracers'
     284       WRITE(lunout,*) trim(modname),': The choice of advection schema for one or more tracers'
    230285       WRITE(lunout,*) 'makes it necessary to add tracers'
    231        WRITE(lunout,*) nqtrue,' is the number of true tracers'
    232        WRITE(lunout,*) nqtot, ' is the total number of tracers needed'
     286       WRITE(lunout,*) trim(modname)//': ',nqtrue,' is the number of true tracers'
     287       WRITE(lunout,*) trim(modname)//': ',nqtot, ' is the total number of tracers needed'
    233288
    234289    ELSE
     
    258313          iadv(new_iq)=11
    259314       ELSE
    260           WRITE(lunout,*)'This choice of advection schema is not available'
     315          WRITE(lunout,*)trim(modname),': This choice of advection schema is not available',iq,hadv(iq),vadv(iq)
     316
    261317          CALL abort_gcm('infotrac_init','Bad choice of advection schema - 2',1)
    262318       END IF
     
    265321       tname(new_iq)= tnom_0(iq)
    266322       IF (iadv(new_iq)==0) THEN
    267           ttext(new_iq)=str1(1:lnblnk(str1))
     323          ttext(new_iq)=trim(str1)
    268324       ELSE
    269           ttext(new_iq)=str1(1:lnblnk(str1))//descrq(iadv(new_iq))
     325          ttext(new_iq)=trim(tnom_0(iq))//descrq(iadv(new_iq))
    270326       END IF
    271327
     
    276332             new_iq=new_iq+1
    277333             iadv(new_iq)=-20
    278              ttext(new_iq)=str2(1:lnblnk(str2))//txts(jq)
    279              tname(new_iq)=str1(1:lnblnk(str1))//txts(jq)
     334             ttext(new_iq)=trim(str2)//txts(jq)
     335             tname(new_iq)=trim(str1)//txts(jq)
    280336          END DO
    281337       ELSE IF (iadv(new_iq)==30) THEN
     
    283339             new_iq=new_iq+1
    284340             iadv(new_iq)=-30
    285              ttext(new_iq)=str2(1:lnblnk(str2))//txtp(jq)
    286              tname(new_iq)=str1(1:lnblnk(str1))//txtp(jq)
     341             ttext(new_iq)=trim(str2)//txtp(jq)
     342             tname(new_iq)=trim(str1)//txtp(jq)
    287343          END DO
    288344       END IF
     
    303359
    304360
    305     WRITE(lunout,*) 'Information stored in infotrac :'
    306     WRITE(lunout,*) 'iadv  niadv tname  ttext :'
     361    WRITE(lunout,*) trim(modname),': Information stored in infotrac :'
     362    WRITE(lunout,*) trim(modname),': iadv  niadv tname  ttext :'
    307363    DO iq=1,nqtot
    308        WRITE(lunout,*) iadv(iq),niadv(iq), tname(iq), ttext(iq)
     364       WRITE(lunout,*) iadv(iq),niadv(iq),&
     365       ' ',trim(tname(iq)),' ',trim(ttext(iq))
    309366    END DO
    310367
     
    315372    DO iq=1,nqtot
    316373       IF (iadv(iq)/=10 .AND. iadv(iq)/=14 .AND. iadv(iq)/=0) THEN
    317           WRITE(lunout,*)'STOP : The option iadv=',iadv(iq),' is not tested in this version of LMDZ'
     374          WRITE(lunout,*)trim(modname),' STOP : The option iadv=',iadv(iq),' is not tested in this version of LMDZ'
    318375          CALL abort_gcm('infotrac_init','In this version only iadv=10 and iadv=14 is tested!',1)
    319376       ELSE IF (iadv(iq)==14 .AND. iq/=1) THEN
    320           WRITE(lunout,*)'STOP : The option iadv=',iadv(iq),' is not tested in this version of LMDZ'
     377          WRITE(lunout,*)trim(modname),'STOP : The option iadv=',iadv(iq),' is not tested in this version of LMDZ'
    321378          CALL abort_gcm('infotrac_init','In this version iadv=14 is only permitted for water vapour!',1)
    322379       END IF
     
    329386    DEALLOCATE(tracnam)
    330387
    331 999 FORMAT (i2,1x,i2,1x,a15)
    332 
    333388  END SUBROUTINE infotrac_init
    334389
Note: See TracChangeset for help on using the changeset viewer.