Ignore:
Timestamp:
Oct 9, 2012, 3:29:15 PM (12 years ago)
Author:
Laurent Fairhead
Message:

Version testing basée sur la r1575


Testing release based on r1575

Location:
LMDZ5/branches/testing
Files:
12 edited

Legend:

Unmodified
Added
Removed
  • LMDZ5/branches/testing

  • LMDZ5/branches/testing/libf/dyn3dpar/ce0l.F90

    r1531 r1664  
    7878#endif
    7979
    80   IF (config_inca /= 'none') THEN
     80  IF (type_trac == 'inca') THEN
    8181#ifdef INCA
    8282      CALL init_const_lmdz( &
  • LMDZ5/branches/testing/libf/dyn3dpar/conf_gcm.F

    r1502 r1664  
    1717      use parallel, ONLY : omp_chunk
    1818      USE control_mod
     19      USE infotrac, ONLY : type_trac
    1920      IMPLICIT NONE
    2021c-----------------------------------------------------------------------
     
    102103      CALL getin('lunout', lunout)
    103104      IF (lunout /= 5 .and. lunout /= 6) THEN
    104         OPEN(lunout,FILE='lmdz.out')
     105        OPEN(UNIT=lunout,FILE='lmdz.out_0000',ACTION='write',
     106     &          STATUS='unknown',FORM='formatted')
     107
    105108      ENDIF
    106109
     
    588591       END IF
    589592       
     593!Config  Key  = type_trac
     594!Config  Desc = Choix de couplage avec model de chimie INCA ou REPROBUS
     595!Config  Def  = lmdz
     596!Config  Help =
     597!Config         'lmdz' = pas de couplage, pur LMDZ
     598!Config         'inca' = model de chime INCA
     599!Config         'repr' = model de chime REPROBUS
     600      type_trac = 'lmdz'
     601      CALL getin('type_trac',type_trac)
     602
     603
    590604!Config  Key  = config_inca
    591605!Config  Desc = Choix de configuration de INCA
     
    659673      write(lunout,*)' tauyy = ', tauyy
    660674      write(lunout,*)' offline = ', offline
     675      write(lunout,*)' type_trac = ', type_trac
    661676      write(lunout,*)' config_inca = ', config_inca
    662677      write(lunout,*)' ok_dynzon = ', ok_dynzon
     
    785800     &         'only the file phystoke.nc will still be created '
    786801       END IF
     802
     803!Config  Key  = type_trac
     804!Config  Desc = Choix de couplage avec model de chimie INCA ou REPROBUS
     805!Config  Def  = lmdz
     806!Config  Help =
     807!Config         'lmdz' = pas de couplage, pur LMDZ
     808!Config         'inca' = model de chime INCA
     809!Config         'repr' = model de chime REPROBUS
     810      type_trac = 'lmdz'
     811      CALL getin('type_trac',type_trac)
    787812
    788813!Config  Key  = config_inca
     
    933958      write(lunout,*)' tauy = ', tauy
    934959      write(lunout,*)' offline = ', offline
     960      write(lunout,*)' type_trac = ', type_trac
    935961      write(lunout,*)' config_inca = ', config_inca
    936962      write(lunout,*)' ok_dynzon = ', ok_dynzon
  • LMDZ5/branches/testing/libf/dyn3dpar/dynredem.F

    r1403 r1664  
    641641#endif
    642642
    643       IF (config_inca /= 'none') THEN
     643      IF (type_trac == 'inca') THEN
    644644! Ajout Anne pour lecture valeurs traceurs dans un fichier start_trac.nc
    645645         ierr_file = NF_OPEN ("start_trac.nc", NF_NOWRITE,nid_trac)
     
    654654      do iq=1,nqtot
    655655
    656          IF (config_inca == 'none') THEN
     656         IF (type_trac /= 'inca') THEN
    657657            ierr = NF_INQ_VARID(nid, tname(iq), nvarid)
    658658            IF (ierr .NE. NF_NOERR) THEN
     
    666666            ierr = NF_PUT_VAR_REAL (nid,nvarid,q(1,1,iq))
    667667#endif
    668         ELSE ! config_inca = 'chem' ou 'aero'
     668        ELSE ! type_trac=inca
    669669! lecture de la valeur du traceur dans start_trac.nc
    670670           IF (ierr_file .ne. 2) THEN
     
    730730#endif
    731731          ENDIF ! (ierr_file .ne. 2)
    732        END IF   ! config_inca
     732       END IF   ! type_trac
    733733     
    734734      ENDDO
  • LMDZ5/branches/testing/libf/dyn3dpar/dynredem_p.F

    r1403 r1664  
    650650#endif
    651651
    652       IF (config_inca /= 'none') THEN
     652      IF (type_trac == 'inca') THEN
    653653! Ajout Anne pour lecture valeurs traceurs dans un fichier start_trac.nc
    654654         inquire(FILE="start_trac.nc", EXIST=exist_file)
     
    667667      do iq=1,nqtot
    668668
    669          IF (config_inca == 'none') THEN
     669         IF (type_trac /= 'inca') THEN
    670670            ierr = NF_INQ_VARID(nid, tname(iq), nvarid)
    671671            IF (ierr .NE. NF_NOERR) THEN
     
    678678            ierr = NF_PUT_VAR_REAL (nid,nvarid,q(1,1,iq))
    679679#endif
    680         ELSE ! config_inca = 'chem' ou 'aero'
     680        ELSE ! type_trac = inca
    681681! lecture de la valeur du traceur dans start_trac.nc
    682682           IF (ierr_file .ne. 2) THEN
     
    732732#endif
    733733          ENDIF ! (ierr_file .ne. 2)
    734        END IF   ! config_inca
     734       END IF   ! type_trac
    735735     
    736736      ENDDO
  • LMDZ5/branches/testing/libf/dyn3dpar/exner_hyb_p.F

    r1520 r1664  
    125125      endif
    126126!$OMP END MASTER
    127 
     127!$OMP BARRIER
    128128        jjb=jj_begin
    129129        jje=jj_end
     
    171171      endif
    172172c$OMP END MASTER
     173c$OMP BARRIER
    173174c
    174175c
  • LMDZ5/branches/testing/libf/dyn3dpar/exner_milieu_p.F

    r1521 r1664  
    121121      endif
    122122!$OMP END MASTER
    123 
     123!$OMP BARRIER
    124124        jjb=jj_begin
    125125        jje=jj_end
     
    169169      endif
    170170c$OMP END MASTER
     171c$OMP BARRIER
    171172c
    172173c
  • LMDZ5/branches/testing/libf/dyn3dpar/gcm.F

    r1520 r1664  
    240240#endif
    241241
    242       IF (config_inca /= 'none') THEN
     242      IF (type_trac == 'inca') THEN
    243243#ifdef INCA
    244244         call init_const_lmdz(
     
    459459c   Initialisation des dimensions d'INCA :
    460460c   --------------------------------------
    461       IF (config_inca /= 'none') THEN
     461      IF (type_trac == 'inca') THEN
    462462!$OMP PARALLEL
    463463#ifdef INCA
  • LMDZ5/branches/testing/libf/dyn3dpar/infotrac.F90

    r1454 r1664  
    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
    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
     
    119149         nbtr=nqtrue
    120150       endif
    121     ELSE
    122        ! nbtr has been read from INCA by init_cont_lmdz() in gcm.F
     151    ELSE ! type_trac=inca
     152       ! nbtr has been read from INCA by init_const_lmdz() in gcm.F
    123153       nqtrue=nbtr+2
    124154    END IF
     
    128158       CALL abort_gcm('infotrac_init','Not enough tracers',1)
    129159    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       
    130168!
    131169! Allocate variables depending on nqtrue and nbtr
     
    162200!    Get choice of advection schema from file tracer.def or from INCA
    163201!---------------------------------------------------------------------
    164     IF (type_trac == 'lmdz') THEN
     202    IF (type_trac == 'lmdz' .OR. type_trac == 'repr') THEN
    165203       IF(ierr.EQ.0) THEN
    166204          ! Continue to read tracer.def
  • LMDZ5/branches/testing/libf/dyn3dpar/iniacademic.F90

    r1520 r1664  
    115115  endif
    116116
    117   academic_case: if (iflag_phys == 2) then
     117  academic_case: if (iflag_phys >= 2) then
    118118     ! initializations
    119119
     
    208208     IF (.NOT. read_start) THEN
    209209        ! surface pressure
    210         ps(:)=preff
     210        if (iflag_phys>2) then
     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
     217           ps(:)=preff
     218        endif
     219       
    211220        ! ground geopotential
    212221        phis(:)=0.
  • LMDZ5/branches/testing/libf/dyn3dpar/leapfrog_p.F

    r1520 r1664  
    189189
    190190      INTEGER :: true_itau
    191       LOGICAL :: verbose=.true.
    192191      INTEGER :: iapptrac
    193192      INTEGER :: AdjustCount
     
    407406           call allgather_timer_average
    408407
    409         if (Verbose) then
     408        if (prt_level > 9) then
    410409       
    411410        print *,'*********************************'
  • LMDZ5/branches/testing/libf/dyn3dpar/parallel.F90

    r1492 r1664  
    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))
Note: See TracChangeset for help on using the changeset viewer.