Changeset 1120 for trunk/LMDZ.TITAN/libf


Ignore:
Timestamp:
Dec 3, 2013, 3:05:40 PM (11 years ago)
Author:
slebonnois
Message:

SL: Titan and Venus modifications following a modif in dyn3d[par].

Location:
trunk/LMDZ.TITAN/libf/phytitan
Files:
4 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.TITAN/libf/phytitan/clesphys.h

    r1056 r1120  
    1010       LOGICAL ok_orodr,ok_orolf,ok_gw_nonoro
    1111       INTEGER nbapp_rad, nbapp_chim, iflag_con, iflag_ajs
    12        REAL    ecritphy
     12       REAL    ecriphy
    1313       INTEGER lev_histmth, lev_histday
    1414       REAL    solaire
     
    3939
    4040       COMMON/clesphys_r/                                               &
    41      &     ecritphy, solaire, z0, lmixmin, ksta, inertie, emis,         &
     41     &     ecriphy, solaire, z0, lmixmin, ksta, inertie, emis,          &
    4242     &     tx,tcorrect,p_prodaer,xnuf,xvis,xir
    4343
  • trunk/LMDZ.TITAN/libf/phytitan/conf_phys.F90

    r1056 r1120  
    139139!Config         en jours.
    140140!
    141        ecritphy = 1.
    142        CALL getin('ecritphy', ecritphy)
     141       ecriphy = 1.
     142       CALL getin('ecritphy', ecriphy)
    143143!
    144144!Config Key  = if_ebil
     
    479479  write(numout,*)' Sortie journaliere = ', ok_journe
    480480  write(numout,*)' Sortie instantanee = ', ok_instan
    481   write(numout,*)' frequence sorties = ', ecritphy 
     481  write(numout,*)' frequence sorties = ', ecriphy 
    482482  write(numout,*)' Sortie bilan d energie, if_ebil =', if_ebil
    483483  write(numout,*)' Duree de l annee = ',year_day
  • trunk/LMDZ.TITAN/libf/phytitan/physiq.F

    r1072 r1120  
    591591         ENDIF
    592592
    593          ecrit_ins = NINT(RDAY/dtime*ecritphy)  ! Fraction de jour reglable
     593         ecrit_ins = NINT(RDAY/dtime*ecriphy)  ! Fraction de jour reglable
    594594         IF (ok_instan) THEN
    595595         WRITE(lunout,*)'La frequence de sortie instant. est de ',
  • trunk/LMDZ.TITAN/libf/phytitan/rcm1d.F

    r1056 r1120  
    44      use control_mod
    55      use comgeomphy
     6      USE phys_state_var_mod
    67      use cpdet_mod, only: ini_cpdet
    78      IMPLICIT NONE
     
    2223c   
    2324c=======================================================================
    24 
    25 c Version TITAN a tester et verifier 
    26 c  - verifier pour Ls...
    27 c  - faire un profile.F ...
    2825
    2926#include "dimensions.h"
     
    5249      REAL play(llm)   ! Pressure at the middle of the layers (Pa)
    5350      REAL plev(llm+1) ! intermediate pressure levels (pa)
    54       REAL psurf,tsurf(1)     
     51      REAL psurf     
    5552      REAL u(llm),v(llm)  ! zonal, meridional wind
    5653      REAL gru,grv   ! prescribed "geostrophic" background wind
    5754      REAL temp(llm)   ! temperature at the middle of the layers
    5855      REAL,allocatable :: q(:,:) ! tracer mixing ratio (e.g. kg/kg)
    59       REAL tsoil(nsoilmx)   ! subsurface soik temperature (K)
    6056      REAL zlay(llm)   ! altitude estimee dans les couches (km)
    6157      REAL long(1),lati(1),area(1)
    6258      REAL cufi(1),cvfi(1)
    63       REAL phisfi(1),albedo(1)
    64       REAL solsw(1),sollwdown(1),dlw(1),radsol(1)
    65       REAL zmea(1), zstd(1)
    66       REAL zsig(1), zgam(1), zthe(1)
    67       REAL zpic(1), zval(1)
     59      REAL phisfi(1)
    6860
    6961c    Physical and dynamical tandencies (e.g.  m.s-2, K/s, Pa/s)
     
    8577      COMMON/cpdetvenus/cppdyn,nu_venus,t0_venus
    8678      REAL cppdyn,nu_venus,t0_venus
    87       real pi
    8879
    8980c=======================================================================
     
    168159c     print*,nbapp_rad
    169160c LU DANS PHYSIQ.DEF...
    170       nbapp_rad = 10.
     161      nbapp_rad = 100.
    171162
    172163      PRINT *,'nombre de jours simules ?'
     
    176167      ndt=ndt*day_step     
    177168      dtphys=daysec/day_step 
    178       dtime=dtphys
    179169
    180170c Pression de surface sur la planete
     
    196186      long(1)=0.E+0
    197187
    198 c  Initialisation albedo
    199 c  ----------------------
    200 c ne sert pas ici...
    201       albedo(1)=0.3
    202 c      PRINT *,'Albedo du sol nu ?'
    203 c      READ(unit,*) albedo(1)
    204 c      PRINT *,albedo(1)
    205 
    206188c   Initialisation speciales "physiq"
    207189c   ---------------------------------
     
    209191      CALL init_phys_lmdz(iim,jjm,llm,1,(/1/))
    210192      call initcomgeomphy
    211       call infotrac_init
    212193      call ini_cpdet
    213194
     
    271252      pks=cpp*(psurf/preff)**rcp
    272253
     254c  init des variables pour phyredem
     255c  --------------------------------
     256      call phys_state_var_init
     257
    273258c  profil de temperature et altitude au premier appel
    274259c  --------------------------------------------------
     
    289274      print*,"               Pression        Altitude     Temperature"
    290275      ilayer=1
    291       tsurf(1)=tmp3(0)
     276      ftsol(1)=tmp3(0)
    292277       temp(1)=tmp3(1)
    293278       zlay(1)=tmp3(1)*tmp1(1)
    294       print*,"           0",tsurf(1)
     279      print*,"           0",ftsol(1)
    295280      print*,ilayer,play(ilayer),zlay(ilayer),temp(ilayer)
    296281      DO ilayer=2,nlayer
     
    303288c     ~~~~~~~~~~~~~~~~~~~~~~~
    304289      DO isoil=1,nsoil
    305          tsoil(isoil)=93.
     290         ftsoil(1,isoil)=ftsol(1)
    306291      ENDDO
    307292
     
    331316         print*,'Ls=',zls*180./pi
    332317
     318c  Initialisation albedo
     319c  ----------------------
     320
     321      falbe(1)=0.3
     322
    333323c  Ecriture de "startphy.nc"
    334324c  -------------------------
     
    338328
    339329      solsw(1)    = 0.
    340       sollwdown(1)= 0.
    341       dlw(1)      = 0.
     330      sollw(1)    = 0.
     331      fder(1)     = 0.
    342332      radsol(1)   = 0.
    343333     
     
    345335      soil_model  = .true.
    346336
    347       call phyredem("startphy.nc  ",
    348      .              lati,long,
    349      .              tsurf,tsoil,albedo,
    350      .              solsw,sollwdown,dlw,radsol,
    351      .    zmea, zstd, zsig, zgam, zthe, zpic, zval,
    352      .              temp)
     337      call phyredem("startphy.nc")
     338
     339c  deallocation des variables phyredem
     340c  -----------------------------------
     341      call phys_state_var_end
    353342
    354343c=======================================================================
     
    463452
    464453      OPEN(11,file='profile.new')
    465       write (11,*) tsurf
    466454      DO ilayer=1,nlayer
    467455        write (11,*) zlay(ilayer),temp(ilayer),tmp1(ilayer)
     
    476464#include "../dyn3d/disvert_noterre.F"
    477465#include "../dyn3d/abort_gcm.F"
    478 !#include "../dyn3d/dump2d.F"
    479 
    480 c***********************************************************************
    481       function ssum(n,sx,incx)
    482 c
    483       IMPLICIT NONE
    484 c
    485       integer n,incx,i,ix
    486       real ssum,sx((n-1)*incx+1)
    487 c
    488       ssum=0.
    489       ix=1
    490       do 10 i=1,n
    491          ssum=ssum+sx(ix)
    492          ix=ix+incx
    493 10    continue
    494 c
    495       return
    496       end
Note: See TracChangeset for help on using the changeset viewer.