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
Files:
5 added
6 deleted
5 edited
6 copied
31 moved

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.COMMON/libf/dyn3d/leapfrog.F

    r1302 r1403  
    170170      logical ok_sync
    171171      parameter (ok_sync = .true.)
    172       logical physic
     172      logical physics
    173173
    174174      data callinigrads/.true./
     
    251251
    252252      itau = 0
    253       physic=.true.
    254       if (iflag_phys==0.or.iflag_phys==2) physic=.false.
     253      physics=.true.
     254      if (iflag_phys==0.or.iflag_phys==2) physics=.false.
    255255
    256256c      iday = day_ini+itau/day_step
     
    362362     s        apdiss = .TRUE.
    363363         IF( MOD(itau,iphysiq ).EQ.0.AND..NOT.forward
    364      s          .and. physic                        ) apphys = .TRUE.
     364     s          .and. physics                        ) apphys = .TRUE.
    365365      ELSE
    366366      ! Leapfrog/Matsuno time stepping
     
    368368         IF( MOD(itau+1,dissip_period).EQ.0 .AND. .NOT. forward )
    369369     s        apdiss = .TRUE.
    370          IF( MOD(itau+1,iphysiq).EQ.0.AND.physic       ) apphys=.TRUE.
     370         IF( MOD(itau+1,iphysiq).EQ.0.AND.physics       ) apphys=.TRUE.
    371371      END IF
    372372
  • trunk/LMDZ.COMMON/libf/dyn3d/logic.h

    r1302 r1403  
    1212     &  ,read_start,ok_guide,ok_strato,tidal,ok_gradsfile               &
    1313     &  ,ok_limit,ok_etat0,hybrid                                       &
    14      &  ,moyzon_mu,moyzon_ch
     14     &  ,moyzon_mu,moyzon_ch,grireg,physic
    1515
    1616      COMMON/logici/ iflag_phys,iflag_trac
     
    2626
    2727      integer iflag_phys,iflag_trac
     28
     29! stuff for compatibility with Mars/Generic old dyn cores. To be cleaned!
     30      logical grireg,physic
     31
    2832!-----------------------------------------------------------------------
  • 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
  • trunk/LMDZ.COMMON/libf/dyn3dpar/leapfrog_p.F

    r1391 r1403  
    163163      REAL :: secondes
    164164      real :: rdaym_ini
    165       logical :: physic
     165      logical :: physics
    166166      LOGICAL first,callinigrads
    167167
     
    256256
    257257      itau = 0
    258       physic=.true.
    259       if (iflag_phys==0.or.iflag_phys==2) physic=.false.
     258      physics=.true.
     259      if (iflag_phys==0.or.iflag_phys==2) physics=.false.
    260260!      iday = day_ini+itau/day_step
    261261!      time = REAL(itau-(iday-day_ini)*day_step)/day_step+time_0
     
    433433     s        apdiss = .TRUE.
    434434         IF( MOD(itau,iphysiq ).EQ.0.AND..NOT.forward
    435      s          .and. physic                        ) apphys = .TRUE.
     435     s          .and. physics                        ) apphys = .TRUE.
    436436      ELSE
    437437      ! Leapfrog/Matsuno time stepping
     
    439439         IF( MOD(itau+1,dissip_period).EQ.0 .AND. .NOT. forward )
    440440     s        apdiss = .TRUE.
    441          IF( MOD(itau+1,iphysiq).EQ.0.AND.physic) apphys=.TRUE.
     441         IF( MOD(itau+1,iphysiq).EQ.0.AND.physics) apphys=.TRUE.
    442442      END IF
    443443
  • trunk/LMDZ.COMMON/libf/dynlonlat_phylonlat/calfis.F

    r1401 r1403  
    137137      REAL,INTENT(OUT) :: pdpsfi(iip1,jjp1) ! tendency on surface pressure (Pa/s)
    138138
    139 
     139#ifndef CPP_PARA
    140140c    Local variables :
    141141c    -----------------
     
    955955      firstcal = .FALSE.
    956956
    957       RETURN
     957#endif
     958! of #ifndef CPP_PARA
    958959      END
  • trunk/LMDZ.COMMON/libf/dynlonlat_phylonlat/calfis_p.F

    r1401 r1403  
    3333!      USE IOPHY
    3434#endif
     35#ifdef CPP_PARA
    3536      USE parallel_lmdz, ONLY : omp_chunk, using_mpi, AllGather_Field
    3637      USE Write_Field
    3738      Use Write_field_p
    3839      USE Times
     40      USE cpdet_mod, only: tpot2t_p, t2tpot_p
     41! used only for zonal averages
     42      USE moyzon_mod
     43#endif
    3944      USE infotrac, ONLY: nqtot, niadv, tname
    4045      USE control_mod, ONLY: planet_type, nsplit_phys
    41       USE cpdet_mod, only: tpot2t_p, t2tpot_p
    42 
    43 ! used only for zonal averages
    44       USE moyzon_mod
    4546
    4647      IMPLICIT NONE
     
    147148      REAL,INTENT(OUT) :: pdpsfi(iip1,jjp1) ! tendency on surface pressure (Pa/s)
    148149
     150#ifdef CPP_PARA
    149151#ifdef CPP_PHYS
    150152c    Local variables :
     
    895897     .             ztfi_omp,
    896898     .             zqfi_omp,
    897 c#ifdef INCA
    898899     .             flxwfi_omp,
    899 c#endif
    900900     .             zdufi_omp,
    901901     .             zdvfi_omp,
     
    14401440#endif
    14411441! of #ifdef CPP_PHYS
    1442       RETURN
     1442#endif
     1443! of #ifdef CPP_PARA
    14431444      END
  • trunk/LMDZ.COMMON/libf/dynlonlat_phylonlat/gr_dyn_fi_p.F

    r1401 r1403  
    33!
    44      SUBROUTINE gr_dyn_fi_p(nfield,im,jm,ngrid,pdyn,pfi)
    5 #ifdef CPP_PHYS
     5#ifdef CPP_PARA
    66! Interface with parallel physics,
    77      USE mod_interface_dyn_phys
     
    4040c$OMP END DO NOWAIT
    4141#endif
    42 ! of #ifdef CPP_PHYS
     42! of #ifdef CPP_PARA
    4343      RETURN
    4444      END
  • trunk/LMDZ.COMMON/libf/dynlonlat_phylonlat/gr_fi_dyn_p.F

    r1401 r1403  
    33!
    44      SUBROUTINE gr_fi_dyn_p(nfield,ngrid,im,jm,pfi,pdyn)
    5 #ifdef CPP_PHYS
     5#ifdef CPP_PARA
    66! Interface with parallel physics,
    77      USE mod_interface_dyn_phys
    88      USE dimphy
    9       use parallel_lmdz
     9      USE parallel_lmdz
    1010      IMPLICIT NONE
    1111c=======================================================================
     
    5252c$OMP END DO NOWAIT
    5353#endif
    54 ! of #ifdef CPP_PHYS
     54! of #ifdef CPP_PARA
    5555      RETURN
    5656      END
Note: See TracChangeset for help on using the changeset viewer.