Ignore:
Timestamp:
Jan 3, 2016, 11:16:34 AM (8 years ago)
Author:
Ehouarn Millour
Message:

Improving the physics/dynamics interface:

  • 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.F90" into module "physiq_mod.F90" for better control of "physiq" arguments. Extracted embeded "gr_fi_ecrit" as self-standing routine (but note that this routine actually only works in serial mode).

EM

File:
1 moved

Legend:

Unmodified
Added
Removed
  • LMDZ5/trunk/libf/phylmd/physiq_mod.F90

    r2416 r2418  
     1!
    12! $Id$
     3!
    24!#define IO_DEBUG
     5MODULE physiq_mod
     6
     7IMPLICIT NONE
     8
     9CONTAINS
    310
    411SUBROUTINE physiq (nlon,nlev, &
     
    44704477  !      first=.false.
    44714478
    4472   RETURN
     4479
    44734480END SUBROUTINE physiq
     4481
    44744482FUNCTION qcheck(klon,klev,paprs,q,ql,aire)
    44754483  IMPLICIT none
     
    44994507  qcheck = qtotal/zx
    45004508  !
    4501   RETURN
    45024509END FUNCTION qcheck
    4503 SUBROUTINE gr_fi_ecrit(nfield,nlon,iim,jjmp1,fi,ecrit)
    4504   IMPLICIT none
    4505   !
    4506   ! Tranformer une variable de la grille physique a
    4507   ! la grille d'ecriture
    4508   !
    4509   INTEGER nfield,nlon,iim,jjmp1, jjm
    4510   REAL fi(nlon,nfield), ecrit(iim*jjmp1,nfield)
    4511   !
    4512   INTEGER i, n, ig
    4513   !
    4514   jjm = jjmp1 - 1
    4515   DO n = 1, nfield
    4516      DO i=1,iim
    4517         ecrit(i,n) = fi(1,n)
    4518         ecrit(i+jjm*iim,n) = fi(nlon,n)
    4519      ENDDO
    4520      DO ig = 1, nlon - 2
    4521         ecrit(iim+ig,n) = fi(1+ig,n)
    4522      ENDDO
    4523   ENDDO
    4524   RETURN
    4525   END SUBROUTINE gr_fi_ecrit
    4526 
     4510
     4511END MODULE physiq_mod
Note: See TracChangeset for help on using the changeset viewer.