Ignore:
Timestamp:
Sep 16, 2018, 5:52:25 PM (6 years ago)
Author:
oboucher
Message:

Fields can now be passed to ORCHIDEE through surf_land_orchidee.
Fields are compressed in pbl_surface_mod and uncompressed in surf_land_orchidee.
Cosmetic changes, including in surf_land_mod.

File:
1 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/trunk/libf/phylmd/surf_land_orchidee_mod.F90

    r3102 r3391  
    2626  USE mod_grid_phy_lmdz
    2727  USE mod_phys_lmdz_para, mpi_root_rank=>mpi_master
     28  USE carbon_cycle_mod, ONLY : nbcf_in_orc, nbcf_out, fields_in, yfields_in, yfields_out, cfname_in, cfname_out
    2829
    2930  IMPLICIT NONE
     
    4849       veget, lai, height )
    4950
    50 
    5151    USE mod_surf_para
    5252    USE mod_synchro_omp
    53     USE carbon_cycle_mod, ONLY : carbon_cycle_cpl
     53    USE carbon_cycle_mod
    5454    USE indice_sol_mod
    5555    USE print_control_mod, ONLY: lunout
     
    9696!   ps           pression au sol
    9797!   radsol       rayonnement net aus sol (LW + SW)
    98 !   
    9998!
    10099! output:
     
    113112    INCLUDE "YOMCST.h"
    114113    INCLUDE "dimpft.h"
    115 
    116 
    117  
    118114!
    119115! Parametres d'entree
     
    149145    REAL, DIMENSION(klon,nvm_lmdz), INTENT(OUT) :: height
    150146
    151 
    152147! Local
    153148!****************************************************************************************
    154     INTEGER                                   :: ij, jj, igrid, ireal, index
     149    INTEGER                                   :: ij, jj, igrid, ireal, index, nb
    155150    INTEGER                                   :: error
    156151    REAL, DIMENSION(klon)                     :: swdown_vrai
     
    365360! carbon_cycle_cpl not possible with this interface and version of ORHCHIDEE
    366361!
    367        IF (carbon_cycle_cpl) THEN
    368           abort_message='carbon_cycle_cpl not yet possible with this interface of ORCHIDEE'
    369           CALL abort_physic(modname,abort_message,1)
    370        END IF
     362! >> PC
     363!       IF (carbon_cycle_cpl) THEN
     364!          abort_message='carbon_cycle_cpl not yet possible with this interface of ORCHIDEE'
     365!          CALL abort_physic(modname,abort_message,1)
     366!       END IF
     367! << PC
    371368       
    372369    ENDIF                          ! (fin debut)
    373370 
    374 
    375371!
    376372! Appel a la routine sols continentaux
     
    413409       IF (knon > 0) THEN
    414410
     411         print *,'OB before intersurf=', SIZE(cfname_in), SIZE(cfname_out)
    415412#ifdef CPP_VEGET
    416413         CALL intersurf_initialize_gathered (itime+itau_phy-1, nbp_lon, nbp_lat, knon, ktindex, dtime, &
     
    421418               evap, fluxsens, fluxlat, coastalflow, riverflow, &
    422419               tsol_rad, tsurf_new, qsurf, albedo_out, emis_new, z0m_new, &   
    423                lon_scat, lat_scat, q2m, t2m, z0h_new, nvm_orch)
     420! >> PC
     421               !lon_scat, lat_scat, q2m, t2m, z0h_new, nvm_orch)
     422               lon_scat, lat_scat, q2m, t2m, z0h_new, nvm_orch, &
     423               field_out_names=cfname_out, field_in_names=cfname_in(1:nbcf_in_orc))
     424! << PC
    424425#endif         
    425426       ENDIF
     
    430431
    431432    ENDIF
    432 
    433433   
    434434!  swdown_vrai(1:knon) = swnet(1:knon)/(1. - albedo_keep(1:knon))
     
    452452            lon_scat, lat_scat, q2m, t2m, z0h_new(1:knon),&
    453453            veget(1:knon,:),lai(1:knon,:),height(1:knon,:),&
     454            fields_out=yfields_out(1:knon,1:nbcf_out),  &
     455            fields_in=yfields_in(1:knon,1:nbcf_in_orc), &
    454456            coszang=yrmu0(1:knon))
    455457#endif       
     
    480482    IF (debut) CALL Finalize_surf_para
    481483
     484! >> PC
     485! Decompressing variables into LMDz for the module carbon_cycle_mod
     486! nbcf_in can be zero, in which case the loop does not operate
     487! fields_in can then used elsewhere in the model
     488     
     489     fields_in(:,:)=0.0
     490
     491     DO nb=1, nbcf_in_orc
     492       DO igrid = 1, knon
     493        ireal = knindex(igrid)
     494        fields_in(ireal,nb)=yfields_in(igrid,nb)
     495       ENDDO
     496       WRITE(*,*) 'surf_land_orchidee_mod --- yfields_in :',cfname_in(nb)
     497     ENDDO
     498! >> PC
    482499   
    483500  END SUBROUTINE surf_land_orchidee
     
    541558!****************************************************************************************
    542559   
    543    
    544560    IF (is_omp_root) THEN         
    545561     
     
    566582      ENDDO
    567583    ENDIF
    568    
    569584   
    570585  END SUBROUTINE Get_orchidee_communicator
     
    628643       off_ini(4,3) =  1          ; off_ini(5,3) = nbp_lon           ; off_ini(6,3) = nbp_lon - 1
    629644       off_ini(7,3) = -1          ; off_ini(8,3) = - nbp_lon - 1
    630 !
    631645!
    632646! Attention aux poles
     
    645659         ENDDO
    646660       ELSE
    647        print*,'sonia : knon_glo,ij,jj', knon_glo, ij,jj
    648661       
    649662       DO igrid = 1, knon_glo
Note: See TracChangeset for help on using the changeset viewer.