Changeset 1549 for trunk/LMDZ.TITAN/libf


Ignore:
Timestamp:
May 6, 2016, 12:30:29 PM (9 years ago)
Author:
emillour
Message:

All GCMs:
Further adaptations to keep up with changes in LMDZ5 concerning
physics/dynamics separation (up to rev r2420 of LMDZ5)

  • all physics packages:
  • added module callphysiq_mod.F90 in dynphy_lonlat/phy* which contains the routine "call_physiq" which is called by calfis* and calls the physics. This way different "physiq" routine from different physics packages may be called: The calfis* routines now exposes all available fields that might be transmitted to physiq but which is actually send (ie: expected/needed by physiq) is decided in call_physiq.
  • turned "physiq.F[90]" into module "physiq_mod.F[90]" for better control of "physiq" arguments. for phyvenus/phytitan, extracted gr_fi_ecrit from physiq.F as gr_fi_ecrit.F90 (note that it can only work in serial).
  • misc:
  • updated wxios.F90 to keep up with LMDZ5 modifications.
  • dyn3d_common:
  • infotrac.F90 keep up with LMDZ5 modifications (cosmetics)
  • dyn3d:
  • gcm.F90: cosmetic cleanup.
  • leapfrog.F90: fix computation of date as function of itau.
  • dyn3dpar:
  • gcm.F: cosmetic cleanup.
  • leapfrog_p.F90: fix computation of date as function of itau.

NB: physics are given the date corresponding to the end of the
physics step.

  • dynphy_lonlat:
  • calfis.F : added computation of relative wind vorticity.
  • calfis_p.F: added computation of relative wind vorticity (input required by Earth physics)

EM

Location:
trunk/LMDZ.TITAN/libf/phytitan
Files:
1 added
1 edited
1 moved

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.TITAN/libf/phytitan/dyn1d/rcm1d.F

    r1548 r1549  
    1313      USE iniphysiq_mod, ONLY: iniphysiq
    1414      USE mod_const_mpi, ONLY: comm_lmdz
     15      USE physiq_mod, ONLY: physiq
    1516      IMPLICIT NONE
    1617
     
    6768      REAL du(llm),dv(llm),dtemp(llm)
    6869      REAL dudyn(llm),dvdyn(llm),dtempdyn(llm)
    69       REAL dpsurf   
     70      REAL dpsurf(1)   
    7071      REAL,allocatable :: dq(:,:)
    7172
     
    439440c       ----------------------------------------------------------
    440441
    441            psurf=psurf+dtphys*dpsurf   ! evolution de la pression de surface
     442           psurf=psurf+dtphys*dpsurf(1)   ! evolution de la pression de surface
    442443           DO ilevel=1,nlevel
    443444             plev(ilevel)=ap(ilevel)+psurf*bp(ilevel)
  • trunk/LMDZ.TITAN/libf/phytitan/physiq_mod.F

    r1548 r1549  
    11!
    2 ! $Header: /home/cvsroot/LMDZ4/libf/phylmd/physiq.F,v 1.8 2005/02/24 09:58:18 fairhead Exp $
     2! $Id: $
    33!
    4 c
     4      MODULE physiq_mod
     5
     6      IMPLICIT NONE
     7
     8      CONTAINS
     9
    510      SUBROUTINE physiq (nlon,nlev,nqmax,
    611     .            debut,lafin,rjourvrai,gmtime,pdtphys,
     
    16221627      ENDIF
    16231628     
    1624       RETURN
    1625       END
    1626 
    1627 
    1628 
    1629 ***********************************************************************
    1630 ***********************************************************************
    1631 ***********************************************************************
    1632 ***********************************************************************
    1633 ***********************************************************************
    1634 ***********************************************************************
    1635 ***********************************************************************
    1636 ***********************************************************************
    1637 
    1638       SUBROUTINE gr_fi_ecrit(nfield,nlon,iim,jjmp1,fi,ecrit)
    1639       IMPLICIT none
    1640 c
    1641 c Tranformer une variable de la grille physique a
    1642 c la grille d'ecriture
    1643 c
    1644       INTEGER nfield,nlon,iim,jjmp1, jjm
    1645       REAL fi(nlon,nfield), ecrit(iim*jjmp1,nfield)
    1646 c
    1647       INTEGER i, n, ig
    1648 c
    1649       jjm = jjmp1 - 1
    1650       DO n = 1, nfield
    1651          DO i=1,iim
    1652             ecrit(i,n) = fi(1,n)
    1653             ecrit(i+jjm*iim,n) = fi(nlon,n)
    1654          ENDDO
    1655          DO ig = 1, nlon - 2
    1656            ecrit(iim+ig,n) = fi(1+ig,n)
    1657          ENDDO
    1658       ENDDO
    1659       RETURN
    1660       END
     1629      END SUBROUTINE physiq
     1630
     1631      END MODULE physiq_mod
     1632
Note: See TracChangeset for help on using the changeset viewer.