Changeset 927 for LMDZ4/trunk/libf


Ignore:
Timestamp:
Mar 14, 2008, 1:12:38 PM (17 years ago)
Author:
lmdzadmin
Message:

Ajout variables zmax0, f0 dans le startphy.nc FH
IM

Location:
LMDZ4/trunk/libf
Files:
7 edited

Legend:

Unmodified
Added
Removed
  • LMDZ4/trunk/libf/dyn3d/etat0_netcdf.F

    r886 r927  
    120120
    121121      REAL, DIMENSION(klon,klev,nbsrf) :: pbl_tke ! turb kinetic energy
     122      REAL, DIMENSION(klon) :: zmax0, f0
    122123      REAL :: dummy(klon, nbsrf)
    123124      !
     
    687688      ocean = "slab"
    688689      pbl_tke(:,:,:) = 1.e-8
     690      zmax0(:) = 40.
     691      f0(:) = 1.e-5
    689692
    690693      call fonte_neige_init(run_off_lic_0)
     
    698701     $    radsol,
    699702     $    zmea, zstd, zsig, zgam, zthe, zpic, zval, rugsrel,
    700      $    t_ancien, q_ancien, rnebcon, ratqs, clwcon, pbl_tke )
     703     $    t_ancien, q_ancien, rnebcon, ratqs, clwcon, pbl_tke,
     704     $    zmax0, f0 )
    701705
    702706
  • LMDZ4/trunk/libf/phylmd/calltherm.F90

    r879 r927  
    77     &      ,d_u_ajs,d_v_ajs,d_t_ajs,d_q_ajs  &
    88     &      ,fm_therm,entr_therm,zqasc,clwcon0,lmax,ratqscth,  &
    9      &       ratqsdiff,zqsatth,Ale_bl,Alp_bl,lalim_conv,wght_th)
     9     &       ratqsdiff,zqsatth,Ale_bl,Alp_bl,lalim_conv,wght_th, &
     10     &       zmax0,f0)
    1011
    1112      implicit none
     
    5960      real Alp(klon)
    6061!RC
     62      !on garde le zmax du pas de temps precedent
     63      real zmax0(klon), f0(klon)
    6164!********************************************************
    6265
     
    171174     &      ,ratqscth,ratqsdiff,zqsatth  &
    172175     &      ,r_aspect_thermals,l_mix_thermals,w2di_thermals  &
    173      &      ,tho_thermals,Ale,Alp,lalim_conv,wght_th)
     176     &      ,tho_thermals,Ale,Alp,lalim_conv,wght_th &
     177     &      ,zmax0,f0)
    174178         endif
    175179
  • LMDZ4/trunk/libf/phylmd/phyetat0.F

    r888 r927  
    1313     .           rugsrel_p,tabcntr0,
    1414     .           t_ancien_p,q_ancien_p,ancien_ok_p, rnebcon_p, ratqs_p,
    15      .           clwcon_p,pbl_tke_p)
     15     .           clwcon_p,pbl_tke_p, zmax0_p, f0_p)
    1616
    1717      USE dimphy
     
    4848      REAL tsol_p(klon,nbsrf)
    4949      REAL pbl_tke_p(klon,klev,nbsrf)
     50      REAL zmax0_p(klon), f0_p(klon)
    5051      REAL tsoil_p(klon,nsoilmx,nbsrf)
    5152      REAL tslab_p(klon), seaice_p(klon)
     
    8586      REAL tsol(klon_glo,nbsrf)
    8687      REAL pbl_tke(klon_glo,klev,nbsrf)
     88      REAL zmax0(klon), f0(klon)
    8789      REAL tsoil(klon_glo,nsoilmx,nbsrf)
    8890cIM "slab" ocean
     
    15381540         ENDDO
    15391541      ENDIF
    1540 
     1542c
     1543c zmax0
     1544      ierr = NF_INQ_VARID (nid, "ZMAX0", nvarid)
     1545      IF (ierr.NE.NF_NOERR) THEN
     1546         PRINT*, "phyetat0: Le champ <ZMAX0> est absent"
     1547         PRINT*, "Depart legerement fausse. Mais je continue"
     1548         zmax0=40.
     1549      ELSE
     1550#ifdef NC_DOUBLE
     1551         ierr = NF_GET_VAR_DOUBLE(nid, nvarid, zmax0)
     1552#else
     1553         ierr = NF_GET_VAR_REAL(nid, nvarid, zmax0)
     1554#endif
     1555         IF (ierr.NE.NF_NOERR) THEN
     1556            PRINT*, "phyetat0: Lecture echouee pour <ZMAX0>"
     1557            CALL abort
     1558         ENDIF
     1559      ENDIF
     1560      xmin = 1.0E+20
     1561      xmax = -1.0E+20
     1562      xmin = MINval(zmax0)
     1563      xmax = MAXval(zmax0)
     1564      PRINT*,'(ecart-type) zmax0:', xmin, xmax
     1565c
     1566c           f0(ig)=1.e-5
     1567c f0
     1568      ierr = NF_INQ_VARID (nid, "f0", nvarid)
     1569      IF (ierr.NE.NF_NOERR) THEN
     1570         PRINT*, "phyetat0: Le champ <f0> est absent"
     1571         PRINT*, "Depart legerement fausse. Mais je continue"
     1572         f0=1.e-5
     1573      ELSE
     1574#ifdef NC_DOUBLE
     1575         ierr = NF_GET_VAR_DOUBLE(nid, nvarid, f0)
     1576#else
     1577         ierr = NF_GET_VAR_REAL(nid, nvarid, f0)
     1578#endif
     1579         IF (ierr.NE.NF_NOERR) THEN
     1580            PRINT*, "phyetat0: Lecture echouee pour <f0>"
     1581            CALL abort
     1582         ENDIF
     1583      ENDIF
     1584      xmin = 1.0E+20
     1585      xmax = -1.0E+20
     1586      xmin = MINval(f0)
     1587      xmax = MAXval(f0)
     1588      PRINT*,'(ecart-type) f0:', xmin, xmax
    15411589c
    15421590c Fermer le fichier:
     
    15751623         call Scatter( pbl_tke,pbl_tke_p)
    15761624      endif
     1625      call Scatter( zmax0,zmax0_p)
     1626      call Scatter( f0,f0_p)
    15771627      call Scatter( tsoil,tsoil_p)
    15781628      call Scatter( tslab,tslab_p)
  • LMDZ4/trunk/libf/phylmd/phyredem.F

    r888 r927  
    1010     .           zgam_p,zthe_p,zpic_p,zval_p,rugsrel_p,
    1111     .           t_ancien_p, q_ancien_p, rnebcon_p, ratqs_p, clwcon_p,
    12      .           pbl_tke_p)
     12     .           pbl_tke_p, zmax0_p, f0_p)
    1313
    1414      USE dimphy
     
    3939      REAL tsol_p(klon,nbsrf)
    4040      REAL pbl_tke_p(klon,klev,nbsrf)
     41      REAL zmax0_p(klon), f0_p(klon)
    4142      REAL tsoil_p(klon,nsoilmx,nbsrf)
    4243      CHARACTER*6 ocean
     
    7374      REAL tsol(klon_glo,nbsrf)
    7475      REAL pbl_tke(klon_glo,klev,nbsrf)
     76      REAL zmax0(klon_glo), f0(klon)
    7577      REAL tsoil(klon_glo,nsoilmx,nbsrf)
    7678      REAL tslab(klon_glo), seaice(klon_glo)
     
    139141      call Gather( tsol_p,tsol)
    140142      call Gather( pbl_tke_p,pbl_tke)
     143      call Gather( zmax0_p,zmax0)
     144      call Gather( f0_p,f0)
    141145      call Gather( tsoil_p,tsoil)
    142146      call Gather( tslab_p,tslab)
  • LMDZ4/trunk/libf/phylmd/phys_state_var_mod.F90

    r913 r927  
    2929      REAL, ALLOCATABLE, SAVE :: ratqs(:,:)
    3030      REAL, ALLOCATABLE, SAVE :: pbl_tke(:,:,:) ! turb kinetic energy
     31      REAL, ALLOCATABLE, SAVE :: zmax0(:), f0(:) !
    3132
    3233CONTAINS
     
    5657      ALLOCATE( ratqs(klon,klev))
    5758      ALLOCATE(pbl_tke(klon,klev+1,nbsrf))
     59      ALLOCATE(zmax0(klon), f0(klon))
    5860
    5961END SUBROUTINE phys_state_var_init
     
    7274      deallocate( rugoro, t_ancien, q_ancien, clwcon, rnebcon )
    7375      deallocate( ratqs, pbl_tke )
     76      deallocate( zmax0, f0 )
    7477
    7578END SUBROUTINE phys_state_var_end
  • LMDZ4/trunk/libf/phylmd/physiq.F

    r913 r927  
    16401640     .       zmea,zstd,zsig,zgam,zthe,zpic,zval,rugoro,tabcntr0,
    16411641     .       t_ancien, q_ancien, ancien_ok, rnebcon, ratqs,clwcon,
    1642      .       pbl_tke)
     1642     .       pbl_tke, zmax0, f0)
    16431643
    16441644
     
    26452645     s      ,ratqsdiff,zqsatth
    26462646con rajoute ale et alp, et les caracteristiques de la couche alim
    2647      s      ,Ale_bl,Alp_bl,lalim_conv,wght_th)
     2647     s      ,Ale_bl,Alp_bl,lalim_conv,wght_th, zmax0, f0)
    26482648         endif
    26492649
     
    37573757     .      zmea,zstd,zsig,zgam,zthe,zpic,zval,rugoro,
    37583758     .      t_ancien, q_ancien, rnebcon, ratqs, clwcon,
    3759      .      pbl_tke)
     3759     .      pbl_tke, zmax0, f0)
    37603760         open(97,form="unformatted",file="finbin")
    37613761         write(97) u_seri,v_seri,t_seri,q_seri
  • LMDZ4/trunk/libf/phylmd/thermcell_main.F90

    r926 r927  
    99     &                  ,ratqscth,ratqsdiff,zqsatth  &
    1010     &                  ,r_aspect,l_mix,w2di,tho &
    11      &                  ,Ale_bl,Alp_bl,lalim_conv,wght_th)
     11     &                  ,Ale_bl,Alp_bl,lalim_conv,wght_th &
     12     &                  ,zmax0, f0)
    1213
    1314      IMPLICIT NONE
     
    7475!on garde le zmax du pas de temps precedent
    7576      real zmax0(klon)
    76       save zmax0
     77!FH/IM     save zmax0
    7778
    7879      real zlev(klon,klev+1),zlay(klon,klev)
     
    130131      real alim_star(klon,klev)
    131132      real f(klon), f0(klon)
    132       save f0
     133!FH/IM     save f0
    133134      real zlevinter(klon)
    134135      logical debut
     
    174175!
    175176      do ig=1,klon     
    176       if ((debut).or.((.not.debut).and.(f0(ig).lt.1.e-10))) then
     177!FH/IM 130308     if ((debut).or.((.not.debut).and.(f0(ig).lt.1.e-10))) then
     178      if ((.not.debut).and.(f0(ig).lt.1.e-10)) then
    177179            f0(ig)=1.e-5
    178180            zmax0(ig)=40.
     
    180182      endif
    181183      enddo
    182 
    183184
    184185
Note: See TracChangeset for help on using the changeset viewer.