Ignore:
Timestamp:
Jun 24, 2020, 11:27:16 AM (4 years ago)
Author:
dubos
Message:

simple_physics : turn zc, zd, capcal, fluxgrd into local temporaries

File:
1 edited

Legend:

Unmodified
Added
Removed
  • dynamico_lmdz/simple_physics/phyparam/physics/phyparam_mod.F90

    r4242 r4245  
    33  USE callkeys
    44  USE comgeomfi
    5   USE surface
    65  IMPLICIT NONE
    76  PRIVATE
     
    2524       &            pdu,pdv,pdt,pdpsrf) BIND(C, name='phyparam_phyparam')
    2625    USE phys_const, ONLY : g, rcp, r, unjours
     26    USE surface, ONLY : soil_forward, soil_backward
     27    USE surface, ONLY : z0, inertie, emissiv, albedo  ! precomputed
     28    USE surface, ONLY : tsurf, tsoil ! state variables
     29!    USE surface, ONLY : capcal, fluxgrd, zc, zd ! should be temporaries
    2730    USE turbulence, ONLY : vdif
    2831    USE convection, ONLY : convadj
     
    6669
    6770    !    Local variables :
    68     REAL, DIMENSION(ngrid) :: mu0
    69     INTEGER :: j,l,ig,nlevel,igout
    70     LOGICAL :: lwrite
    71     !
    72     REAL :: zday, zdtime
    73     REAL zh(ngrid,nlayer),z1,z2
    74     REAL zzlev(ngrid,nlayer+1),zzlay(ngrid,nlayer)
    75     REAL zdvfr(ngrid,nlayer),zdufr(ngrid,nlayer)
    76     REAL zdhfr(ngrid,nlayer),zdtsrf(ngrid),zdtsrfr(ngrid)
    77     REAL zflubid(ngrid),zpmer(ngrid)
    78     REAL zpopsk(ngrid,nlayer)
     71    REAL :: zh(ngrid,nlayer),      & ! potential temperature
     72         &  zpopsk(ngrid,nlayer),  & ! Exner function
     73         &  zzlev(ngrid,nlayer+1), & ! altitude of interfaces
     74         &  zzlay(ngrid,nlayer),   & ! altitude of full levels
     75         &  fluxrad(ngrid),        & ! radiative flux at surface
     76         &  zc(ngrid, nsoilmx),    & ! LU coefficients for soil implicit solve
     77         &  zd(ngrid, nsoilmx),    &
     78         &  fluxgrd(ngrid),        & ! heat flux from deep soil
     79         &  capcal(ngrid)          & ! effective heat capacity of soil
     80         &  zdufr(ngrid,nlayer),   & ! partial tendencies for zonal velocity,
     81         &  zdvfr(ngrid,nlayer),   & !   meridional velocity,
     82         &  zdhfr(ngrid,nlayer),   & !   potential temperature,
     83         &  zdtsrfr(ngrid),        & !   surface temperature
     84         &  zdtsrf(ngrid),         & ! total tendency of surface temperature
     85         &  zflubid(ngrid),        & ! radiative + deep soil fluxes
     86         &  zpmer(ngrid),          & ! sea-level pressure
    7987    REAL zdum1(ngrid,nlayer)
    8088    REAL zdum2(ngrid,nlayer)
    8189    REAL zdum3(ngrid,nlayer)
    82     REAL fluxrad(ngrid)
     90
     91    INTEGER :: j,l,ig,nlevel,igout
     92    LOGICAL :: lwrite
     93    REAL    :: zday, zdtime, z1, z2
    8394
    8495    WRITELOG(*,*) 'latitude0', ngrid, lati(1:2), lati(ngrid-1:ngrid)
     
    8899    IF (ngrid.NE.ngridmax) THEN
    89100       PRINT*,'STOP in inifis'
    90        PRINT*,'Probleme de dimenesions :'
     101       PRINT*,'Probleme de dimensions :'
    91102       PRINT*,'ngrid     = ',ngrid
    92103       PRINT*,'ngridmax   = ',ngridmax
     
    159170    ENDDO
    160171
     172    !-------------------------------------------------------------
     173    !  soil temperatures : 1st half of implicit time integration
     174    !  forward sweep from deep ground to surface
     175    !  yields LU coefficients zc,zd and capcal, fluxgrd
     176    !   ----------------------------------------------------------
     177
     178    IF (callsoil) THEN
     179       CALL soil_forward(ngrid,nsoilmx, ptimestep, inertie, tsurf, tsoil, &
     180         &            zc, zd, capcal, fluxgrd)
     181
     182!       CALL soil_new(ngrid,nsoilmx,ptimestep,inertie, &
     183!            tsurf, tsoil, capcal,fluxgrd)
     184!       CALL soil(ngrid,nsoilmx,.false.,inertie, &
     185!            &          ptimestep,tsurf,tsoil,capcal,fluxgrd)
     186    ELSE
     187       capcal(:)  = capcal_nosoil
     188       fluxgrd(:) = 0.
     189    ENDIF
     190
     191    IF(lverbose) THEN
     192       WRITELOG(*,*) 'Surface Heat capacity, conduction Flux, Ts'
     193       WRITELOG(*,*) capcal(igout), fluxgrd(igout), tsurf(igout)
     194       LOG_DBG('phyparam')
     195    ENDIF
     196
    161197    !-----------------------------------------------------------------------
    162198    !    2. Compute radiative tendencies :
     
    169205    !-----------------------------------------------------------------------
    170206    !    3. Vertical diffusion (turbulent mixing):
    171     !    -----------------------------------------
     207    ! Kz is computed then vertical diffusion is integrated in time implicitly
     208    ! using a linear relationship between surface heat flux and air temperature
     209    ! in lowest level (Robin-type BC)
     210    !    -------------------------------------------------------------------
    172211    !
    173212    IF(calldifv) THEN
     
    212251       ENDDO
    213252    ENDIF
     253
     254    !-------------------------------------------------------------
     255    !   soil temperatures : 2nd half of implicit time integration
     256    !   using updated tsurf as input
     257    !   ----------------------------------------------------------
     258
     259    DO ig=1,ngrid
     260       tsurf(ig)=tsurf(ig)+ptimestep*zdtsrf(ig)
     261    ENDDO
     262
     263    WRITE(55,'(2e15.5)') zday,tsurf(ngrid/2+1)
     264
     265    IF (callsoil) THEN
     266       CALL soil_backward(ngrid,nsoilmx, zc,zd, tsurf,tsoil)
     267       IF(lverbose) THEN
     268          WRITELOG(*,*) 'Surface Ts, dTs, dt'
     269          WRITELOG(*,*) tsurf(igout), zdtsrf(igout), ptimestep
     270          LOG_DBG('phyparam')
     271       ENDIF
     272    END IF
     273
     274
    214275    !
    215276    !-----------------------------------------------------------------------
     
    243304       ENDDO
    244305
    245     ENDIF
    246 
    247     !-----------------------------------------------------------------------
    248     !   On ajoute les tendances physiques a la temperature du sol:
    249     !   ---------------------------------------------------------------
    250 
    251     DO ig=1,ngrid
    252        tsurf(ig)=tsurf(ig)+ptimestep*zdtsrf(ig)
    253     ENDDO
    254 
    255     WRITE(55,'(2e15.5)') zday,tsurf(ngrid/2+1)
    256 
    257     !-----------------------------------------------------------------------
    258     !   soil temperatures:
    259     !   --------------------
    260 
    261     IF (callsoil) THEN
    262        CALL soil(ngrid,nsoilmx,.false.,inertie, &
    263             &          ptimestep,tsurf,tsoil,capcal,fluxgrd)
    264        IF(lverbose) THEN
    265           WRITELOG(*,*) 'Surface Heat capacity,conduction Flux, Ts, dTs, dt'
    266           WRITELOG(*,*) capcal(igout), fluxgrd(igout), tsurf(igout), &
    267                &        zdtsrf(igout), ptimestep
    268           LOG_DBG('phyparam')
    269        ENDIF
    270306    ENDIF
    271307
     
    309345    !$cython wrapper def alloc(ngrid, nlayer) : phy.phyparam_alloc(ngrid, nlayer)
    310346    USE astronomy, ONLY : iniorbit
     347    USE surface
    311348    INTEGER, INTENT(IN), VALUE :: ngrid, nlayer
     349    ! allocate precomputed arrays
     350    ALLOCATE(rnatur(ngrid), albedo(ngrid), emissiv(ngrid))
     351    ALLOCATE(z0(ngrid),inertie(ngrid))
    312352    ! allocate arrays for internal state
    313353    ALLOCATE(tsurf(ngrid))
    314354    ALLOCATE(tsoil(ngrid,nsoilmx))
    315     ! we could avoid the arrays below with a different implementation of surface / radiation / turbulence coupling
    316     ALLOCATE(capcal(ngrid),fluxgrd(ngrid))
    317     ALLOCATE(zc(ngrid,nsoilmx),zd(ngrid,nsoilmx))
    318     ! allocate precomputed arrays
    319     ALLOCATE(rnatur(ngrid), albedo(ngrid), emissiv(ngrid))
    320     ALLOCATE(z0(ngrid),inertie(ngrid))
     355    IF(.FALSE.) THEN ! arrays below are now local temporaries in phyparam
     356       ALLOCATE(capcal(ngrid),fluxgrd(ngrid))
     357       ALLOCATE(zc(ngrid,nsoilmx),zd(ngrid,nsoilmx))
     358    END IF
    321359    CALL iniorbit
    322360  END SUBROUTINE alloc
     
    326364    !$cython wrapper def precompute() : phy.phyparam_precompute()
    327365    ! precompute time-independent arrays
     366    USE surface
    328367    rnatur(:)  = 1.
    329368    inertie(:) = (1.-rnatur(:))*I_mer+rnatur(:)*I_ter
     
    337376    !$cython wrapper def coldstart (ngrid, timestep): phy.phyparam_coldstart(ngrid, timestep)
    338377    ! create internal state to start a run without a restart file
     378    USE surface
    339379    INTEGER, INTENT(IN), VALUE :: ngrid
    340380    REAL, INTENT(IN),    VALUE :: ptimestep
     
    343383    icount=0
    344384    IF(callsoil) THEN
    345        ! initializes zc, zd, capcal, fluxgrd
    346        CALL soil(ngrid,nsoilmx,.TRUE.,inertie, &
    347             &          ptimestep,tsurf,tsoil,capcal,fluxgrd)
     385       IF(.FALSE.) THEN
     386          ! init_soil is now called by iniphyparam
     387          ! initializes zc, zd, capcal, fluxgrd
     388          CALL soil(ngrid,nsoilmx,.TRUE.,inertie, &
     389               &          ptimestep,tsurf,tsoil,capcal,fluxgrd)
     390       END IF
     391       IF(.FALSE.) THEN ! soil_forward is now called by phyparam
     392          CALL soil_forward(ngrid, nsoilmx, ptimestep, inertie, tsurf, tsoil, &
     393               &            zc, zd, capcal, fluxgrd)
     394       END IF
    348395    ELSE
    349396       WRITELOG(*,*) 'WARNING!!! Thermal conduction in the soil turned off'
Note: See TracChangeset for help on using the changeset viewer.