Changeset 295


Ignore:
Timestamp:
Nov 26, 2001, 2:47:57 PM (23 years ago)
Author:
lmdzadmin
Message:

Tag version 0 qui marche en couple/force
LF

Location:
LMDZ.3.3/branches/rel-LF
Files:
11 edited

Legend:

Unmodified
Added
Removed
  • LMDZ.3.3/branches/rel-LF/libf/bibio/initdynav.F

    r177 r295  
    119119     .             32, 'ave(X)', t_ops, t_wrt)
    120120C
     121C  Temperature potentielle
     122C
     123      call histdef(fileid, 'theta', 'temperature potentielle', 'K',
     124     .             iip1, jjp1, thoriid, llm, 1, llm, zvertiid,
     125     .             32, 'ave(X)', 7200., 7200.)
     126
     127
     128C
    121129C  Geopotentiel
    122130C
  • LMDZ.3.3/branches/rel-LF/libf/bibio/writedynav.F

    r29 r295  
    7171      ndex2d = 0
    7272      ok_sync = .TRUE.
     73      us = 999.999
     74      vs = 999.999
     75      tm = 999.999
     76      vnat = 999.999
     77      unat = 999.999
    7378
    7479C Passage aux composantes naturelles du vent
     
    8994      call histwrite(histid, 'v', time, vs,
    9095     .               iip1*jjp1*llm, ndex3d)
     96C
     97C  Temperature potentielle moyennee
     98C
     99      call histwrite(histid, 'theta', time, teta,
     100     .                iip1*jjp1*llm, ndex3d)
    91101C
    92102C  Temperature moyennee
  • LMDZ.3.3/branches/rel-LF/libf/dyn3d/abort_gcm.F

    r206 r295  
    2020      call histclo
    2121      call restclo
     22c     call getin_dump
    2223c     call histclo(2)
    2324c     call histclo(3)
  • LMDZ.3.3/branches/rel-LF/libf/dyn3d/gcm.F

    r232 r295  
    306306      t_ops = iecri * daysec
    307307      t_wrt = iecri * daysec
    308       CALL inithist(dynhist_file,day_ini,anne_ini,time_step,
    309      .              t_ops, t_wrt, nqmx, histid, histvid)
     308C      CALL inithist(dynhist_file,day_ini,anne_ini,time_step,
     309c     .              t_ops, t_wrt, nqmx, histid, histvid)
    310310
    311311      t_ops = iperiod * time_step
     
    595595               nbetat = nbetatdem
    596596       CALL geopot  ( ip1jmp1, teta  , pk , pks,  phis  , phi        )
    597        CALL writehist( histid, histvid, nqmx, itau,vcov ,
    598      ,                          ucov,teta,phi,q,masse,ps,phis)
     597c       CALL writehist( histid, histvid, nqmx, itau,vcov ,
     598c     ,                          ucov,teta,phi,q,masse,ps,phis)
    599599
    600600
     
    682682                  nbetat = nbetatdem
    683683       CALL geopot  ( ip1jmp1, teta  , pk , pks,  phis  , phi       )
    684        CALL writehist( histid, histvid, nqmx, itau,vcov ,
    685      ,                          ucov,teta,phi,q,masse,ps,phis)
     684c       CALL writehist( histid, histvid, nqmx, itau,vcov ,
     685c     ,                          ucov,teta,phi,q,masse,ps,phis)
    686686               ENDIF
    687687
  • LMDZ.3.3/branches/rel-LF/libf/phylmd/clmain.F

    r293 r295  
    197197      LOGICAL first_appel
    198198      SAVE first_appel
    199       DATA first_appel/.true./
     199      DATA first_appel/.false./
    200200      LOGICAL debugindex
    201201      SAVE debugindex
    202       DATA debugindex/.true./
     202      DATA debugindex/.false./
    203203#include "temps.h"
    204204     
     
    354354      ENDDO
    355355c
    356       write(*,*)'CLMAIN, nsrf, knon =',nsrf, knon
     356c      write(*,*)'CLMAIN, nsrf, knon =',nsrf, knon
    357357c
    358358c variables pour avoir une sortie IOIPSL des INDEX
     
    434434      CALL coefkz2(nsrf, knon, ypaprs, ypplay,yt,
    435435     .                  ycoefm0, ycoefh0)
    436       write(*,*)'Cdrag maximal = ',maxval(ycoefh(:,1)),
    437      .                               maxval(ycoefh0(:,1))
    438436      DO k = 1, klev
    439437      DO i = 1, knon
     
    443441      ENDDO
    444442
    445       write(*,*)'Cdrag maximal = ',maxloc(ycoefh(:,1)),
    446      .                             maxval(ycoefh(:,1))
    447443c
    448444c
  • LMDZ.3.3/branches/rel-LF/libf/phylmd/interface_surf.F90

    r290 r295  
    188188  integer, save        :: error
    189189  integer              :: ii, index
    190   logical,save              :: check = .true.
     190  logical,save              :: check = .false.
    191191  real, dimension(klon):: cal, beta, dif_grnd, capsol
    192192!!$PB  real, parameter      :: calice=1.0/(5.1444e+06*0.15), tau_gl=86400.*5.
     
    332332     call albsno(klon,knon,dtime,agesno(:),alb_neig(:), precip_snow(:)) 
    333333     where (snow(1 : knon) .LT. 0.0001) agesno(1 : knon) = 0.
    334      zfra(1:knon) = max(0.0,min(1.0,snow/(snow+10.0)))
     334     zfra(1:knon) = max(0.0,min(1.0,snow(1:knon)/(snow(1:knon)+10.0)))
    335335     alb_new(1 : knon)  = alb_neig(1 : knon) *zfra(1:knon) + &
    336336    &                     alb_new(1 : knon)*(1.0-zfra(1:knon))
     
    519519      CALL albsno(klon,knon,dtime,agesno(:),alb_neig(:), precip_snow(:)) 
    520520      WHERE (snow(1 : knon) .LT. 0.0001) agesno(1 : knon) = 0.
    521       zfra(1:knon) = MAX(0.0,MIN(1.0,snow/(snow+10.0)))
     521      zfra(1:knon) = MAX(0.0,MIN(1.0,snow(1:knon)/(snow(1:knon)+10.0)))
    522522      alb_new(1 : knon) = alb_neig(1 : knon) *zfra(1:knon) + &
    523523     &                    0.6 * (1.0-zfra(1:knon))
     
    589589     CALL albsno(klon,knon,dtime,agesno(:),alb_neig(:), precip_snow(:)) 
    590590     WHERE (snow(1 : knon) .LT. 0.0001) agesno(1 : knon) = 0.
    591      zfra(1:knon) = MAX(0.0,MIN(1.0,snow/(snow+10.0)))
     591     zfra(1:knon) = MAX(0.0,MIN(1.0,snow(1:knon)/(snow(1:knon)+10.0)))
    592592     alb_new(1 : knon)  = alb_neig(1 : knon)*zfra(1:knon) + &
    593593    &                     0.6 * (1.0-zfra(1:knon))
     
    744744  character (len = 20) :: modname = 'interfsol'
    745745  character (len = 80) :: abort_message
    746   logical,save              :: check = .TRUE.
     746  logical,save              :: check = .FALSE.
    747747  real, dimension(klon) :: cal, beta, dif_grnd, capsol
    748748! type de couplage dans sechiba
     
    10451045  cdrag(1:knon) = tq_cdrag(1:knon)
    10461046
    1047 !  where(cdrag > 0.01)
    1048 !    cdrag = 0.01
    1049 !  endwhere
     1047   where(cdrag > 0.01)
     1048     cdrag = 0.01
     1049   endwhere
    10501050!  write(*,*)'Cdrag = ',minval(cdrag),maxval(cdrag)
    10511051
     
    11861186  character (len = 20) :: modname = 'interfoce_cpl'
    11871187  character (len = 80) :: abort_message
    1188   logical,save              :: check = .true.
     1188  logical,save              :: check = .FALSE.
    11891189! variables pour moyenner les variables de couplage
    11901190  real, allocatable, dimension(:,:),save :: cpl_sols, cpl_nsol, cpl_rain
     
    17151715  character (len = 20),save :: fich ='limit.nc'
    17161716  logical, save     :: newlmt = .TRUE.
    1717   logical, save     :: check = .true.
     1717  logical, save     :: check = .FALSE.
    17181718! Champs lus dans le fichier de CL
    17191719  real, allocatable , save, dimension(:) :: sst_lu, rug_lu, nat_lu
     
    19591959  character (len = 20),save :: fich ='limit.nc'
    19601960  logical,save     :: newlmt = .false.
    1961   logical,save     :: check = .true.
     1961  logical,save     :: check = .FALSE.
    19621962! Champs lus dans le fichier de CL
    19631963  real, allocatable , save, dimension(:) :: alb_lu, rug_lu
     
    21382138  REAL, parameter :: chasno = 3.334E+05/(2.3867E+06*0.15)
    21392139!
    2140   logical, save         :: check = .true.
     2140  logical, save         :: check = .FALSE.
    21412141  character (len = 20)  :: modname = 'calcul_fluxs'
    21422142  logical, save         :: fonte_neige = .false.
     
    24952495  REAL, parameter :: chasno = 3.334E+05/(2.3867E+06*0.15)
    24962496!
    2497   logical, save         :: check = .true.
     2497  logical, save         :: check = .FALSE.
    24982498  character (len = 20)  :: modname = 'fonte_neige'
    24992499  logical, save         :: neige_fond = .false.
  • LMDZ.3.3/branches/rel-LF/libf/phylmd/physiq.F

    r290 r295  
    371371      REAL albsollw(klon)
    372372      SAVE albsollw                 ! albedo du sol total
     373      REAL albsol1(klon)
     374      SAVE albsol1                 ! albedo du sol total
     375      REAL albsollw1(klon)
     376      SAVE albsollw1                 ! albedo du sol total
    373377
    374378      REAL wo(klon,klev)
     
    576580c
    577581      INTEGER nhori, nvert
    578       REAL zsto, zout, zjulian
     582      REAL zsto, zout
     583      real zjulian
     584      save zjulian
    579585
    580586      character*20 modname
     
    728734ccc         ecrit_ins = NINT(86400./dtime *0.25)  ! 4 fois par jour
    729735         ecrit_ins = NINT(86400./dtime/48.)  ! a chaque pas de temps
     736         ecrit_ins = NINT(86400./dtime/12.)  ! toutes les deux heures
    730737         IF (ok_instan) THEN
    731738         PRINT*, 'La frequence de sortie instant. est de ', ecrit_ins
     
    750757      endif       
    751758c
     759c
     760c Gestion calendrier
     761
     762         CALL ymds2ju(anne_ini, 1, 1, 0.0, zjulian)
     763         zjulian = zjulian + day_ini
     764
    752765c
    753766      IF (ok_journe) THEN
     
    18071820      fder = dlw
    18081821
    1809       CALL clmain(dtime,itap,date0,pctsrf,
     1822      CALL clmain(dtime,itap,zjulian,pctsrf,
    18101823     e            t_seri,q_seri,u_seri,v_seri,
    18111824     e            julien, rmu0,
     
    19711984c$$$     .        ,bbase,dtvpdt1,dtvpdq1,dplcldt,dplcldr,
    19721985c$$$     .        pori_con,plcl_con,dtma_con,dtlcl_con)
    1973           if (1.eq.1) then ! vectorise
     1986          if (0.eq.1) then ! vectorise
    19741987          CALL conemav (dtime,paprs,pplay,t_seri,q_seri,
    19751988     .        u_seri,v_seri,tr_seri,nbtr,
     
    21972210     .               + falblw(i,is_sic) * pctsrf(i,is_sic)
    21982211      ENDDO
     2212!      if (debut) then
     2213!        albsol1 = albsol
     2214!        albsollw1 = albsollw
     2215!      endif
     2216!      albsol = albsol1
     2217!      albsollw = albsollw1
    21992218      CALL radlwsw ! nouveau rayonnement (compatible Arpege-IFS)
    22002219     e            (dist, rmu0, fract, co2_ppm, solaire,
     
    23312350      IF (iflag_con.EQ.4) THEN
    23322351c           on ajoute les tendances calculees par KE43
     2352c$$$ OM on onhibe la convection sur les traceurs
    23332353        DO iq=1, nqmax-2 ! Sandrine a -3 ???
    2334         DO k = 1, nlev
    2335         DO i = 1, klon
    2336           tr_seri(i,k,iq) = tr_seri(i,k,iq) + d_tr(i,k,iq)
    2337         ENDDO
    2338         ENDDO
     2354c$$$ OM on inhibe la convection sur les traceur
     2355c$$$        DO k = 1, nlev
     2356c$$$        DO i = 1, klon
     2357c$$$          tr_seri(i,k,iq) = tr_seri(i,k,iq) + d_tr(i,k,iq)
     2358c$$$        ENDDO
     2359c$$$        ENDDO
    23392360        WRITE(iqn,'(i2.2)') iq
    23402361        CALL minmaxqfi(tr_seri(1,1,iq),0.,1.e33,'couche lim iq='//iqn)
  • LMDZ.3.3/branches/rel-LF/libf/phylmd/phytrac.F

    r235 r295  
    208208     s     inirnpb
    209209      data first,couchelimite,convection,lessivage,sorties
    210      s     /.true.,.true.,.true.,.true.,.true./
     210c$$$ OM Test KE     s     /.true.,.true.,.true.,.true.,.true./
     211     s     /.true.,.true.,.false.,.true.,.true./
    211212c
    212213c======================================================================
  • LMDZ.3.3/branches/rel-LF/liste_des_sources_f90

    r227 r295  
    1        USE IOIPSL
    2 libf/bibio/initdynav.F
     1      USE ioipsl
     2libf/bibio/writedynav.F
    33       USE IOIPSL
    44libf/bibio/initfluxsto.F
    55       USE IOIPSL
    66libf/bibio/inithist.F
    7       USE ioipsl
    8 libf/bibio/writedynav.F
     7       USE IOIPSL
     8libf/bibio/initdynav.F
    99      USE ioipsl
    1010libf/bibio/writehist.F
    1111      USE IOIPSL
    1212libf/dyn3d/abort_gcm.F
    13       USE ioipsl
    14 libf/dyn3d/create_limit.F
    15       USE IOIPSL
    16 libf/dyn3d/dynredem.F
    17       USE ioipsl
    18 libf/dyn3d/etat0_netcdf.F
    1913       USE IOIPSL
    2014libf/dyn3d/fluxstokenc.F
    2115      USE IOIPSL
    22 libf/dyn3d/gcm.F
     16libf/dyn3d/dynredem.F
    2317      USE IOIPSL
    2418libf/dyn3d/gcmtest.F
    2519      USE ioipsl
    26 libf/dyn3d/offline.F
     20libf/dyn3d/offlinenc.F
     21      USE ioipsl
     22libf/dyn3d/etat0_netcdf.F
     23      USE IOIPSL
     24libf/dyn3d/gcm.F
     25      use IOIPSL
     26libf/dyn3d/conf_gcm.F
    2727      USE ioipsl
    2828libf/dyn3d/startvar.F
    2929      USE ioipsl
     30libf/dyn3d/create_limit.F
     31      USE ioipsl
    3032libf/dyn3d/modif_etat0.F
    31       use IOIPSL
    32 libf/dyn3d/conf_gcm.F
    3333      USE ioipsl
    3434libf/phylmd/clmain.F
    35        USE IOIPSL
    36 libf/phylmd/initphysto.F
    3735      USE ioipsl
    3836libf/phylmd/physiq.F
    3937      USE ioipsl
    40 libf/phylmd/phystokenc.F
    41       USE ioipsl
    4238libf/phylmd/phytrac.F
    4339      USE ioipsl
    44 libf/phylmd/donneesgrads.F
    45       USE IOIPSL
    46 libf/phylmd/1DUTILS.h
     40libf/phylmd/phystokenc.F
     41       USE IOIPSL
     42libf/phylmd/initphysto.F
     43libf/bibio/writephys.F90
    4744libf/phylmd/interface_surf.F90
    4845libf/phylmd/conf_phys.F90
  • LMDZ.3.3/branches/rel-LF/tmp

    r227 r295  
    1 g
    2 C
     1clear
     2float0
     3ew
     4R5
  • LMDZ.3.3/branches/rel-LF/tmp90

    r227 r295  
    1        USE IOIPSL
    2 libf/bibio/initdynav.F
     1      USE ioipsl
     2libf/bibio/writedynav.F
    33       USE IOIPSL
    44libf/bibio/initfluxsto.F
    55       USE IOIPSL
    66libf/bibio/inithist.F
    7       USE ioipsl
    8 libf/bibio/writedynav.F
     7       USE IOIPSL
     8libf/bibio/initdynav.F
    99      USE ioipsl
    1010libf/bibio/writehist.F
    1111      USE IOIPSL
    1212libf/dyn3d/abort_gcm.F
    13       USE ioipsl
    14 libf/dyn3d/create_limit.F
    15       USE IOIPSL
    16 libf/dyn3d/dynredem.F
    17       USE ioipsl
    18 libf/dyn3d/etat0_netcdf.F
    1913       USE IOIPSL
    2014libf/dyn3d/fluxstokenc.F
    2115      USE IOIPSL
    22 libf/dyn3d/gcm.F
     16libf/dyn3d/dynredem.F
    2317      USE IOIPSL
    2418libf/dyn3d/gcmtest.F
    2519      USE ioipsl
    26 libf/dyn3d/offline.F
     20libf/dyn3d/offlinenc.F
     21      USE ioipsl
     22libf/dyn3d/etat0_netcdf.F
     23      USE IOIPSL
     24libf/dyn3d/gcm.F
     25      use IOIPSL
     26libf/dyn3d/conf_gcm.F
    2727      USE ioipsl
    2828libf/dyn3d/startvar.F
    2929      USE ioipsl
     30libf/dyn3d/create_limit.F
     31      USE ioipsl
    3032libf/dyn3d/modif_etat0.F
    31       use IOIPSL
    32 libf/dyn3d/conf_gcm.F
    3333      USE ioipsl
    3434libf/phylmd/clmain.F
    35        USE IOIPSL
    36 libf/phylmd/initphysto.F
    3735      USE ioipsl
    3836libf/phylmd/physiq.F
    3937      USE ioipsl
    40 libf/phylmd/phystokenc.F
    41       USE ioipsl
    4238libf/phylmd/phytrac.F
    4339      USE ioipsl
    44 libf/phylmd/donneesgrads.F
    45       USE IOIPSL
    46 libf/phylmd/1DUTILS.h
     40libf/phylmd/phystokenc.F
     41       USE IOIPSL
     42libf/phylmd/initphysto.F
     43libf/bibio/writephys.F90
    4744libf/phylmd/interface_surf.F90
    4845libf/phylmd/conf_phys.F90
Note: See TracChangeset for help on using the changeset viewer.