Changeset 290 for LMDZ.3.3/branches


Ignore:
Timestamp:
Oct 31, 2001, 3:32:18 PM (23 years ago)
Author:
lmdzadmin
Message:

Initialisations de variables Pasb
LF

Location:
LMDZ.3.3/branches/rel-LF/libf/phylmd
Files:
4 edited

Legend:

Unmodified
Added
Removed
  • LMDZ.3.3/branches/rel-LF/libf/phylmd/calcratqs.F

    r230 r290  
    5353      flag_ratqs=1
    5454      flag_ratqs=0
     55        zpt_conv=0.
    5556c
    5657c Appeler le processus de condensation a grande echelle
  • LMDZ.3.3/branches/rel-LF/libf/phylmd/clmain.F

    r280 r290  
    285285      y_flux_u = 0.0
    286286      y_flux_v = 0.0
     287C$$ PB
     288      y_dflux_t = 0.0
     289      y_dflux_q = 0.0
    287290      ytsoil = 999999.
     291      yrugoro = 0.
    288292
    289293      DO nsrf = 1, nbsrf
     
    466470c
    467471c calculer la longueur de rugosite sur ocean
     472      yrugm=0.
    468473      IF (nsrf.EQ.is_oce) THEN
    469474      DO j = 1, knon
     
    499504        ENDDO
    500505      ENDDO
    501      
     506
    502507
    503508      evap(:,nsrf) = - flux_q(:,1,nsrf)
     
    805810C Appel a interfsurf (appel generique) routine d'interface avec la surface
    806811
     812c initialisation
     813       petAcoef =0.
     814        peqAcoef = 0.
     815        petBcoef =0.
     816        peqBcoef = 0.
     817        p1lay =0.
     818       
    807819c      do i = 1, knon
    808         petAcoef=zx_ch(:,1)
    809         peqAcoef=zx_cq(:,1)
    810         petBcoef=zx_dh(:,1)
    811         peqBcoef=zx_dq(:,1)
    812         tq_cdrag=coef(:,1)
    813         temp_air=t(:,1)
    814         epot_air=local_h(:,1)
    815         spechum=q(:,1)
    816         p1lay = pplay(:,1)
    817         zlev1 = delp(:,1)
     820        petAcoef(1:knon) = zx_ch(1:knon,1)
     821        peqAcoef(1:knon) = zx_cq(1:knon,1)
     822        petBcoef(1:knon) =  zx_dh(1:knon,1)
     823        peqBcoef(1:knon) = zx_dq(1:knon,1)
     824        tq_cdrag(1:knon) =coef(1:knon,1)
     825        temp_air(1:knon) =t(1:knon,1)
     826        epot_air(1:knon) =local_h(1:knon,1)
     827        spechum(1:knon)=q(1:knon,1)
     828        p1lay(1:knon) = pplay(1:knon,1)
     829        zlev1(1:knon) = delp(1:knon,1)
    818830        swnet = swdown * (1. - albedo)
    819831c      enddo
  • LMDZ.3.3/branches/rel-LF/libf/phylmd/interface_surf.F90

    r281 r290  
    4242  real, allocatable, dimension(:),save    :: run_off
    4343  real, allocatable, dimension(:),save    :: coastalflow, riverflow
    44 
    45 
     44!!$PB
     45  REAL, ALLOCATABLE, DIMENSION(:,:), SAVE :: tmp_rriv, tmp_rcoa
     46!!$
    4647  CONTAINS
    4748!
     
    268269        call abort_gcm(modname,abort_message,1)
    269270      endif
     271!!$PB
     272      ALLOCATE (tmp_rriv(iim,jjm+1), stat=error)
     273      if (error /= 0) then
     274        abort_message='Pb allocation tmp_rriv'
     275        call abort_gcm(modname,abort_message,1)
     276      endif
     277      ALLOCATE (tmp_rcoa(iim,jjm+1), stat=error)
     278      if (error /= 0) then
     279        abort_message='Pb allocation tmp_rcoa'
     280        call abort_gcm(modname,abort_message,1)
     281      endif
     282!!$
    270283    else if (size(coastalflow) /= knon) then
    271284      write(*,*)'Bizarre, le nombre de points continentaux'
     
    768781  integer :: indi, indj
    769782  integer, dimension(klon) :: ktindex
     783  REAL, dimension(klon) :: bidule
    770784! Essai cdrag
    771785  real, dimension(klon) :: cdrag
     
    10611075     & lon_scat, lat_scat)
    10621076
    1063 !  alb_new(:) = (albedo_out(:,1) + albedo_out(:,2)) / 2.
    1064   alb_new(1:knon) = albedo_out(1:knon,1)
    1065   alblw(1:knon) = albedo_out(1:knon,2)
     1077    bidule=0.
     1078    bidule(1:knon)=riverflow(1:knon)
     1079    call gath2cpl(bidule, tmp_rriv, klon, knon,iim,jjm,                  ktindex)
     1080    bidule=0.
     1081    bidule(1:knon)=coastalflow(1:knon)
     1082    call gath2cpl(bidule, tmp_rcoa, klon, knon,iim,jjm,                  ktindex)
     1083    alb_new(1:knon) = albedo_out(1:knon,1)
     1084    alblw(1:knon) = albedo_out(1:knon,2)
     1085
    10661086
    10671087! Convention orchidee: positif vers le haut
    1068   fluxsens = -1. * fluxsens
    1069   fluxlat  = -1. * fluxlat
     1088  fluxsens(1:knon) = -1. * fluxsens(1:knon)
     1089  fluxlat(1:knon)  = -1. * fluxlat(1:knon)
     1090
    10701091!  evap     = -1. * evap
    10711092
     
    11701191  real, allocatable, dimension(:,:),save :: cpl_snow, cpl_evap, cpl_tsol
    11711192  real, allocatable, dimension(:,:),save :: cpl_fder, cpl_albe, cpl_taux
    1172   real, allocatable, dimension(:,:),save :: cpl_tauy, cpl_rriv, cpl_rcoa
     1193!!$PB  real, allocatable, dimension(:,:),save :: cpl_tauy, cpl_rriv, cpl_rcoa
     1194  real, allocatable, dimension(:,:),save :: cpl_tauy
     1195  real, allocatable, dimension(:,:),save :: cpl_rriv, cpl_rcoa
     1196!!$
    11731197! variables tampons avant le passage au coupleur
    11741198  real, allocatable, dimension(:,:,:),save :: tmp_sols, tmp_nsol, tmp_rain
    11751199  real, allocatable, dimension(:,:,:),save :: tmp_snow, tmp_evap, tmp_tsol
    11761200  real, allocatable, dimension(:,:,:),save :: tmp_fder, tmp_albe, tmp_taux
    1177   real, allocatable, dimension(:,:,:),save :: tmp_tauy, tmp_rriv, tmp_rcoa
     1201!!$  real, allocatable, dimension(:,:,:),save :: tmp_tauy, tmp_rriv, tmp_rcoa
     1202  REAL, ALLOCATABLE, DIMENSION(:,:,:),SAVE :: tmp_tauy
    11781203! variables a passer au coupleur
    11791204  real, dimension(iim, jjm+1) :: wri_sol_ice, wri_sol_sea, wri_nsol_ice
     
    12451270    allocate(cpl_taux(klon,2), stat = error); sum_error = sum_error + error
    12461271    allocate(cpl_tauy(klon,2), stat = error); sum_error = sum_error + error
    1247     allocate(cpl_rcoa(klon,2), stat = error); sum_error = sum_error + error
    1248     allocate(cpl_rriv(klon,2), stat = error); sum_error = sum_error + error
     1272!!$PB
     1273!!$    allocate(cpl_rcoa(klon,2), stat = error); sum_error = sum_error + error
     1274!!$    allocate(cpl_rriv(klon,2), stat = error); sum_error = sum_error + error
     1275    ALLOCATE(cpl_rriv(iim,jjm+1), stat=error); sum_error = sum_error + error
     1276    ALLOCATE(cpl_rcoa(iim,jjm+1), stat=error); sum_error = sum_error + error
     1277!!
    12491278    allocate(read_sst(iim, jjm+1), stat = error); sum_error = sum_error + error
    12501279    allocate(read_sic(iim, jjm+1), stat = error); sum_error = sum_error + error
     
    13471376      cpl_tauy(ig,cpl_index) = cpl_tauy(ig,cpl_index) &
    13481377       &                          + tauy(ig)        / FLOAT(nexca)
    1349       cpl_rriv(ig,cpl_index) = cpl_rriv(ig,cpl_index) &
    1350        &                          + riverflow(ig)   / FLOAT(nexca)/dtime
    1351       cpl_rcoa(ig,cpl_index) = cpl_rcoa(ig,cpl_index) &
    1352        &                          + coastalflow(ig) / FLOAT(nexca)/dtime
     1378!!$      cpl_rriv(ig,cpl_index) = cpl_rriv(ig,cpl_index) &
     1379!!$       &                          + riverflow(ig)   / FLOAT(nexca)/dtime
     1380!!$      cpl_rcoa(ig,cpl_index) = cpl_rcoa(ig,cpl_index) &
     1381!!$       &                          + coastalflow(ig) / FLOAT(nexca)/dtime
    13531382    enddo
     1383    IF (cpl_index .EQ. 1) THEN
     1384        cpl_rriv(:,:) = cpl_rriv(:,:) + tmp_rriv(:,:) / FLOAT(nexca)
     1385        cpl_rcoa(:,:) = cpl_rcoa(:,:) + tmp_rcoa(:,:) / FLOAT(nexca)
     1386    ENDIF
    13541387  endif
    13551388
     
    14481481      allocate(tmp_taux(iim,jjm+1,2), stat=error); sum_error = sum_error + error
    14491482      allocate(tmp_tauy(iim,jjm+1,2), stat=error); sum_error = sum_error + error
    1450       allocate(tmp_rriv(iim,jjm+1,2), stat=error); sum_error = sum_error + error
    1451       allocate(tmp_rcoa(iim,jjm+1,2), stat=error); sum_error = sum_error + error
     1483!!$      allocate(tmp_rriv(iim,jjm+1,2), stat=error); sum_error = sum_error + error
     1484!!$      allocate(tmp_rcoa(iim,jjm+1,2), stat=error); sum_error = sum_error + error
    14521485      if (sum_error /= 0) then
    14531486        abort_message='Pb allocation variables couplees pour l''ecriture'
     
    14711504    call gath2cpl(cpl_taux(1,cpl_index), tmp_taux(1,1,cpl_index), klon, knon,iim,jjm,                  knindex)
    14721505    call gath2cpl(cpl_tauy(1,cpl_index), tmp_tauy(1,1,cpl_index), klon, knon,iim,jjm,                  knindex)
    1473     call gath2cpl(cpl_rriv(1,cpl_index), tmp_rriv(1,1,cpl_index), klon, knon,iim,jjm,                  knindex)
    1474     call gath2cpl(cpl_rcoa(1,cpl_index), tmp_rcoa(1,1,cpl_index), klon, knon,iim,jjm,                  knindex)
     1506!!$    call gath2cpl(cpl_rriv(1,cpl_index), tmp_rriv(1,1,cpl_index), klon, knon,iim,jjm,                  knindex)
     1507!!$    call gath2cpl(cpl_rcoa(1,cpl_index), tmp_rcoa(1,1,cpl_index), klon, knon,iim,jjm,                  knindex)
    14751508
    14761509!
     
    14901523      wri_evap_ice = tmp_evap(:,:,2)
    14911524      wri_evap_sea = tmp_evap(:,:,1)
     1525!!$PB
     1526      wri_rriv = cpl_rriv(:,:)
     1527      wri_rcoa = cpl_rcoa(:,:)
     1528
    14921529      where (tamp_zmasq /= 1.)
    14931530        deno =  tamp_srf(:,:,1) + tamp_srf(:,:,2)
     
    14961533        wri_snow = tmp_snow(:,:,1) * tamp_srf(:,:,1) / deno +    &
    14971534      &            tmp_snow(:,:,2) * tamp_srf(:,:,2) / deno
    1498         wri_rriv = tmp_rriv(:,:,1) * tamp_srf(:,:,1) / deno +    &
    1499       &            tmp_rriv(:,:,2) * tamp_srf(:,:,2) / deno
    1500         wri_rcoa = tmp_rcoa(:,:,1) * tamp_srf(:,:,1) / deno +    &
    1501       &            tmp_rcoa(:,:,2) * tamp_srf(:,:,2) / deno
     1535!!$PB
     1536!!$        wri_rriv = tmp_rriv(:,:,1) * tamp_srf(:,:,1) / deno +    &
     1537!!$      &            tmp_rriv(:,:,2) * tamp_srf(:,:,2) / deno
     1538!!$        wri_rcoa = tmp_rcoa(:,:,1) * tamp_srf(:,:,1) / deno +    &
     1539!!$      &            tmp_rcoa(:,:,2) * tamp_srf(:,:,2) / deno
    15021540        wri_taux = tmp_taux(:,:,1) * tamp_srf(:,:,1) / deno +    &
    15031541      &            tmp_taux(:,:,2) * tamp_srf(:,:,2) / deno
     
    15571595      & wri_nsol_sea, wri_fder_ice, wri_evap_ice, wri_evap_sea, wri_rain, &
    15581596      & wri_snow, wri_rcoa, wri_rriv, wri_tauxx, wri_tauyy, wri_tauzz, &
    1559       & wri_tauxx, wri_tauyy, wri_tauzz,lafin )
     1597      & wri_tauxx, wri_tauyy, wri_tauzz,lafin )
     1598!
    15601599      cpl_sols = 0.; cpl_nsol = 0.; cpl_rain = 0.; cpl_snow = 0.
    15611600      cpl_evap = 0.; cpl_tsol = 0.; cpl_fder = 0.; cpl_albe = 0.
     
    15751614      deallocate(tmp_taux, stat=error); sum_error = sum_error + error
    15761615      deallocate(tmp_tauy, stat=error); sum_error = sum_error + error
    1577       deallocate(tmp_rriv, stat=error); sum_error = sum_error + error
    1578       deallocate(tmp_rcoa, stat=error); sum_error = sum_error + error
     1616!!$PB
     1617!!$      deallocate(tmp_rriv, stat=error); sum_error = sum_error + error
     1618!!$      deallocate(tmp_rcoa, stat=error); sum_error = sum_error + error
    15791619      if (sum_error /= 0) then
    15801620        abort_message='Pb deallocation variables couplees'
     
    21332173! Initialisation
    21342174!
     2175  evap = 0.
     2176  fluxsens=0.
     2177  fluxlat=0.
     2178  dflux_s = 0.
     2179  dflux_l = 0. 
    21352180!
    21362181! zx_qs = qsat en kg/kg
  • LMDZ.3.3/branches/rel-LF/libf/phylmd/physiq.F

    r287 r290  
    16401640c
    16411641      ENDIF
     1642
     1643c$$$PB Positionner date0 pour initialisation de ORCHIDEE
     1644c$$$      date0 = zjulian
     1645      date0 = day_ini
     1646      WRITE(*,*) 'physiq date0 : ',date0
    16421647c
    16431648c
Note: See TracChangeset for help on using the changeset viewer.