Changeset 901


Ignore:
Timestamp:
Mar 12, 2013, 7:36:18 PM (12 years ago)
Author:
slebonnois
Message:

SL: debug pour rcm1d apres parallelisation Venus

Location:
trunk
Files:
3 edited
1 moved

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.VENUS/libf/phyvenus/iostart.F90

    r892 r901  
    2525
    2626    PUBLIC get_field,get_var,put_field,put_var
    27     PUBLIC Open_startphy,close_startphy,open_restartphy,close_restartphy
     27    PUBLIC open_startphy,close_startphy,open_restartphy,close_restartphy
    2828   
    2929CONTAINS
    3030
    31   SUBROUTINE Open_startphy(filename)
     31  SUBROUTINE open_startphy(filename)
    3232  USE netcdf
    3333  USE mod_phys_lmdz_para
     
    4545    ENDIF
    4646   
    47   END SUBROUTINE Open_startphy
     47  END SUBROUTINE open_startphy
    4848
    4949  SUBROUTINE Close_startphy
     
    326326      ENDIF
    327327
    328       ierr = NF90_PUT_ATT (nid_restart, NF90_GLOBAL, "title","Fichier redemmarage physique")
     328      ierr = NF90_PUT_ATT (nid_restart, NF90_GLOBAL, "title","Fichier redemarrage physique")
    329329
    330330      ierr = NF90_DEF_DIM (nid_restart, "index", length, idim1)
  • trunk/LMDZ.VENUS/libf/phyvenus/phys_state_var_mod.F90

    r892 r901  
    137137IMPLICIT NONE
    138138
    139       deallocate(ftsol, falbe)
     139      deallocate(ftsol, ftsoil, falbe)
    140140      deallocate(zmea, zstd, zsig, zgam)
    141141      deallocate(zthe, zpic, zval)
  • trunk/LMDZ.VENUS/libf/phyvenus/rcm1d.F

    r894 r901  
    55      use control_mod
    66      use comgeomphy
     7      USE phys_state_var_mod
    78      IMPLICIT NONE
    89
     
    4849      REAL play(llm)   ! Pressure at the middle of the layers (Pa)
    4950      REAL plev(llm+1) ! intermediate pressure levels (pa)
    50       REAL psurf,tsurf(1)     
     51      REAL psurf     
    5152      REAL u(llm),v(llm)  ! zonal, meridional wind
    5253      REAL gru,grv   ! prescribed "geostrophic" background wind
    5354      REAL temp(llm)   ! temperature at the middle of the layers
    5455      REAL,allocatable :: q(:,:) ! tracer mixing ratio (e.g. kg/kg)
    55       REAL tsoil(nsoilmx)   ! subsurface soik temperature (K)
    5656      REAL zlay(llm)   ! altitude estimee dans les couches (km)
    5757      REAL long(1),lati(1),area(1)
    5858      REAL cufi(1),cvfi(1)
    59       REAL phisfi(1),albedo(1)
    60       REAL solsw(1),sollwdown(1),dlw(1),radsol(1)
    61       REAL zmea(1), zstd(1)
    62       REAL zsig(1), zgam(1), zthe(1)
    63       REAL zpic(1), zval(1)
     59      REAL phisfi(1)
    6460
    6561c    Physical and dynamical tandencies (e.g.  m.s-2, K/s, Pa/s)
     
    196192      long(1)=0.E+0
    197193
    198 c  Initialisation albedo
    199 c  ----------------------
    200 c ne sert pas ici...
    201       albedo(1)=0.1
    202 c      PRINT *,'Albedo du sol nu ?'
    203 c      READ(unit,*) albedo(1)
    204 c      PRINT *,albedo(1)
    205 
    206194c   Initialisation speciales "physiq"
    207195c   ---------------------------------
     
    271259      pks=cpp*(psurf/preff)**rcp
    272260
     261c  init des variables pour phyredem
     262c  --------------------------------
     263      call phys_state_var_init
     264
    273265c  profil de temperature et altitude au premier appel
    274266c  --------------------------------------------------
     
    286278      print*,"               Pression        Altitude     Temperature"
    287279      ilayer=1
    288       tsurf(1)=tmp2(0)
     280      ftsol(1)=tmp2(0)
    289281       temp(1)=tmp2(1)
    290282       zlay(1)=tmp2(1)*tmp1(1)
    291       print*,"           0",tsurf(1)
     283      print*,"           0",ftsol(1)
    292284      print*,ilayer,play(ilayer),zlay(ilayer),temp(ilayer)
    293285      DO ilayer=2,nlayer
     
    300292c     ~~~~~~~~~~~~~~~~~~~~~~~
    301293      DO isoil=1,nsoil
    302          tsoil(isoil)=tsurf(1)
     294         ftsoil(1,isoil)=ftsol(1)
    303295      ENDDO
    304296
     
    323315      zval(1) = 0.
    324316
     317c  Initialisation albedo
     318c  ----------------------
     319
     320      falbe(1)=0.1
     321
    325322c  Ecriture de "startphy.nc"
    326323c  -------------------------
     
    330327
    331328      solsw(1)    = 0.
    332       sollwdown(1)= 0.
    333       dlw(1)      = 0.
     329      sollw(1)    = 0.
     330      fder(1)      = 0.
    334331      radsol(1)   = 0.
    335332     
     
    337334      soil_model  = .true.
    338335
    339       call phyredem("startphy.nc  ",
    340      .              lati,long,
    341      .              tsurf,tsoil,albedo,
    342      .              solsw,sollwdown,dlw,radsol,
    343      .    zmea, zstd, zsig, zgam, zthe, zpic, zval,
    344      .              temp)
     336      call phyredem("startphy.nc")
     337
     338c  deallocation des variables phyredem
     339c  -----------------------------------
     340      call phys_state_var_end
    345341
    346342c=======================================================================
     
    457453
    458454      OPEN(11,file='profile.new')
    459       write (11,*) tsurf
    460455      DO ilayer=1,nlayer
    461456        write (11,*) zlay(ilayer),temp(ilayer),tmp1(ilayer)
Note: See TracChangeset for help on using the changeset viewer.