Ignore:
Timestamp:
Mar 31, 2015, 3:49:07 PM (10 years ago)
Author:
emillour
Message:

All models: Reorganizing the physics/dynamics interface.

  • makelmdz and makelmdz_fcm scripts adapted to handle the new directory settings
  • misc: (replaces what was the "bibio" directory)
  • Should only contain extremely generic (and non physics or dynamics-specific) routines
  • Therefore moved initdynav.F90, initfluxsto.F, inithist.F, writedynav.F90, write_field.F90, writehist.F to "dyn3d_common"
  • dynlonlat_phylonlat: (new interface directory)
  • This directory contains routines relevent to physics/dynamics grid interactions, e.g. routines gr_dyn_fi or gr_fi_dyn and calfis
  • Moreover the dynlonlat_phylonlat contains directories "phy*" corresponding to each physics package "phy*" to be used. These subdirectories should only contain specific interfaces (e.g. iniphysiq) or main programs (e.g. newstart)
  • phy*/dyn1d: this subdirectory contains the 1D model using physics from phy*

EM

Location:
trunk/LMDZ.COMMON/libf/dyn3d_common
Files:
2 edited
6 copied

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.COMMON/libf/dyn3d_common/control_mod.F90

    r1300 r1403  
    5151  real,save :: timestart ! (Mars) time start for run in "start.nc"
    5252
     53  ! stuff for compatibility with Mars/Generic old dyn cores. To be cleaned!
     54  integer,save :: idissip ! (Mars/old dyn) dissipation freq.
     55  real,save :: nday_r ! (Mars/old dyn) number of days to run (possibly including a fraction of day)
     56
     57
    5358END MODULE
  • trunk/LMDZ.COMMON/libf/dyn3d_common/infotrac.F90

    r1391 r1403  
    444444  END SUBROUTINE infotrac_init
    445445
     446! Ehouarn: routine iniadvtrac => from Mars/generic; does essentially the
     447!          same job as infotrac_init. To clean up and merge at some point...
     448      subroutine iniadvtrac(nq,numvanle)
     449!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     450! routine which initializes tracer names and advection schemes
     451! reads these infos from file 'traceur.def' but uses default values
     452! if that file is not found.
     453! Ehouarn Millour. Oct. 2008  (made this LMDZ4-like) for future compatibility
     454!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     455      IMPLICIT NONE
     456
     457!#include "dimensions.h"
     458!#include "advtrac.h"
     459!#include "control.h"
     460
     461! routine arguments:
     462      INTEGER,INTENT(out) :: nq ! number of tracers
     463      INTEGER,INTENT(out) :: numvanle
     464
     465! local variables:
     466      LOGICAL :: first
     467      INTEGER :: iq
     468      INTEGER :: ierr
     469      CHARACTER(len=3) :: qname
     470
     471! Look for file traceur.def
     472      OPEN(90,file='traceur.def',form='formatted',status='old', &
     473              iostat=ierr)
     474      IF (ierr.eq.0) THEN
     475        write(*,*) "iniadvtrac: Reading file traceur.def"
     476        ! read number of tracers:
     477        read(90,*,iostat=ierr) nq
     478        if (ierr.ne.0) then
     479          write(*,*) "iniadvtrac: error reading number of tracers"
     480          write(*,*) "   (first line of traceur.def) "
     481          stop
     482        endif
     483       
     484        ! allocate arrays:
     485        allocate(iadv(nq))
     486        allocate(tname(nq))
     487       
     488        ! initialize advection schemes to Van-Leer for all tracers
     489        do iq=1,nq
     490          iadv(iq)=3 ! Van-Leer
     491        enddo
     492       
     493        do iq=1,nq
     494        ! minimal version, just read in the tracer names, 1 per line
     495          read(90,*,iostat=ierr) tname(iq)
     496          if (ierr.ne.0) then
     497            write(*,*) 'iniadvtrac: error reading tracer names...'
     498            stop
     499          endif
     500        enddo !of do iq=1,nq
     501        close(90) ! done reading tracer names, close file
     502      ENDIF ! of IF (ierr.eq.0)
     503
     504!  ....  Choix  des shemas d'advection pour l'eau et les traceurs  ...
     505!  ...................................................................
     506!
     507!     iadv = 1    shema  transport type "humidite specifique LMD" 
     508!     iadv = 2    shema   amont
     509!     iadv = 3    shema  Van-leer
     510!     iadv = 4    schema  Van-leer + humidite specifique
     511!                        Modif F.Codron
     512!
     513!
     514      DO  iq = 1, nq-1
     515       IF( iadv(iq).EQ.1 ) PRINT *,' Choix du shema humidite specifique'&
     516       ,' pour le traceur no ', iq
     517       IF( iadv(iq).EQ.2 ) PRINT *,' Choix du shema  amont',' pour le'  &
     518       ,' traceur no ', iq
     519       IF( iadv(iq).EQ.3 ) PRINT *,' Choix du shema  Van-Leer ',' pour' &
     520       ,'le traceur no ', iq
     521
     522       IF( iadv(iq).EQ.4 )  THEN
     523         PRINT *,' Le shema  Van-Leer + humidite specifique ',          &
     524       ' est  uniquement pour la vapeur d eau .'
     525         PRINT *,' Corriger iadv( ',iq, ')  et repasser ! '
     526         CALL ABORT
     527       ENDIF
     528
     529       IF( iadv(iq).LE.0.OR.iadv(iq).GT.4 )   THEN
     530        PRINT *,' Erreur dans le choix de iadv (nqtot).Corriger et '    &
     531       ,' repasser car  iadv(iq) = ', iadv(iq)
     532         CALL ABORT
     533       ENDIF
     534      ENDDO
     535
     536       IF( iadv(nq).EQ.1 ) PRINT *,' Choix du shema humidite '          &
     537       ,'specifique pour la vapeur d''eau'
     538       IF( iadv(nq).EQ.2 ) PRINT *,' Choix du shema  amont',' pour la'  &
     539       ,' vapeur d''eau '
     540       IF( iadv(nq).EQ.3 ) PRINT *,' Choix du shema  Van-Leer '         &
     541       ,' pour la vapeur d''eau'
     542       IF( iadv(nq).EQ.4 ) PRINT *,' Choix du shema  Van-Leer + '       &
     543       ,' humidite specifique pour la vapeur d''eau'
     544!
     545       IF( (iadv(nq).LE.0).OR.(iadv(nq).GT.4) )   THEN
     546        PRINT *,' Erreur dans le choix de iadv (nqtot).Corriger et '    &
     547       ,' repasser car  iadv(nqtot) = ', iadv(nqtot)
     548         CALL ABORT
     549       ENDIF
     550
     551      first = .TRUE.
     552      numvanle = nq + 1
     553      DO  iq = 1, nq
     554        IF(((iadv(iq).EQ.3).OR.(iadv(iq).EQ.4)).AND.first ) THEN
     555          numvanle = iq
     556          first    = .FALSE.
     557        ENDIF
     558      ENDDO
     559!
     560      DO  iq = 1, nq
     561
     562      IF( (iadv(iq).NE.3.AND.iadv(iq).NE.4).AND.iq.GT.numvanle )  THEN
     563          PRINT *,' Il y a discontinuite dans le choix du shema de ',   &
     564          'Van-leer pour les traceurs . Corriger et repasser . '
     565           CALL ABORT
     566      ENDIF
     567
     568      ENDDO
     569!
     570      end subroutine iniadvtrac
     571
     572
    446573END MODULE infotrac
Note: See TracChangeset for help on using the changeset viewer.