Changeset 937 for LMDZ4


Ignore:
Timestamp:
Mar 31, 2008, 5:59:23 PM (16 years ago)
Author:
lmdzadmin
Message:

Ajout variables convection (ema_work1, ema_work2) dans startphy.nc
IM

Location:
LMDZ4/trunk/libf
Files:
5 edited

Legend:

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

    r927 r937  
    121121      REAL, DIMENSION(klon,klev,nbsrf) :: pbl_tke ! turb kinetic energy
    122122      REAL, DIMENSION(klon) :: zmax0, f0
     123      REAL, DIMENSION(klon,klev) :: ema_work1, ema_work2
    123124      REAL :: dummy(klon, nbsrf)
    124125      !
     
    690691      zmax0(:) = 40.
    691692      f0(:) = 1.e-5
     693      ema_work1(:,:) = 0.
     694      ema_work2(:,:) = 0.
    692695
    693696      call fonte_neige_init(run_off_lic_0)
     
    702705     $    zmea, zstd, zsig, zgam, zthe, zpic, zval, rugsrel,
    703706     $    t_ancien, q_ancien, rnebcon, ratqs, clwcon, pbl_tke,
    704      $    zmax0, f0 )
     707     $    zmax0, f0, ema_work1, ema_work2 )
    705708
    706709
  • LMDZ4/trunk/libf/phylmd/phyetat0.F

    r927 r937  
    1313     .           rugsrel_p,tabcntr0,
    1414     .           t_ancien_p,q_ancien_p,ancien_ok_p, rnebcon_p, ratqs_p,
    15      .           clwcon_p,pbl_tke_p, zmax0_p, f0_p)
     15     .           clwcon_p,pbl_tke_p, zmax0_p, f0_p,
     16     .           ema_work1_p, ema_work2_p)
    1617
    1718      USE dimphy
     
    4950      REAL pbl_tke_p(klon,klev,nbsrf)
    5051      REAL zmax0_p(klon), f0_p(klon)
     52      REAL ema_work1_p(klon,klev), ema_work2_p(klon,klev)
    5153      REAL tsoil_p(klon,nsoilmx,nbsrf)
    5254      REAL tslab_p(klon), seaice_p(klon)
     
    8789      REAL pbl_tke(klon_glo,klev,nbsrf)
    8890      REAL zmax0(klon), f0(klon)
     91      REAL ema_work1(klon,klev), ema_work2(klon,klev)
    8992      REAL tsoil(klon_glo,nsoilmx,nbsrf)
    9093cIM "slab" ocean
     
    14341437
    14351438c
    1436       ierr = NF_INQ_VARID (nid, "QANCIEN", nvarid)
    1437       IF (ierr.NE.NF_NOERR) THEN
    1438          PRINT*, "phyetat0: Le champ <QANCIEN> est absent"
    1439          PRINT*, "Depart legerement fausse. Mais je continue"
    1440          ancien_ok = .FALSE.
    1441       ELSE
    1442 #ifdef NC_DOUBLE
    1443          ierr = NF_GET_VAR_DOUBLE(nid, nvarid, q_ancien)
    1444 #else
    1445          ierr = NF_GET_VAR_REAL(nid, nvarid, q_ancien)
    1446 #endif
    1447          IF (ierr.NE.NF_NOERR) THEN
    1448             PRINT*, "phyetat0: Lecture echouee pour <QANCIEN>"
    1449             CALL abort
    1450          ENDIF
    1451       ENDIF
    1452 c
    14531439c Lecture ratqs
    14541440c
     
    15871573      xmax = MAXval(f0)
    15881574      PRINT*,'(ecart-type) f0:', xmin, xmax
     1575c
     1576c ema_work1
     1577c
     1578      ierr = NF_INQ_VARID (nid, "EMA_WORK1", nvarid)
     1579      IF (ierr.NE.NF_NOERR) THEN
     1580         PRINT*, "phyetat0: Le champ <EMA_WORK1> est absent"
     1581         PRINT*, "Depart legerement fausse. Mais je continue"
     1582         ema_work1=0.
     1583      ELSE
     1584#ifdef NC_DOUBLE
     1585         ierr = NF_GET_VAR_DOUBLE(nid, nvarid, ema_work1)
     1586#else
     1587         ierr = NF_GET_VAR_REAL(nid, nvarid, ema_work1)
     1588#endif
     1589         IF (ierr.NE.NF_NOERR) THEN
     1590            PRINT*, "phyetat0: Lecture echouee pour <EMA_WORK1>"
     1591            CALL abort
     1592         ENDIF
     1593           xmin = 1.0E+20
     1594           xmax = -1.0E+20
     1595           DO k = 1, klev
     1596           DO i = 1, klon
     1597              xmin = MIN(ema_work1(i,k),xmin)
     1598              xmax = MAX(ema_work1(i,k),xmax)
     1599           ENDDO
     1600           ENDDO
     1601           PRINT*,'ema_work1:', xmin, xmax
     1602      ENDIF
     1603c
     1604c ema_work2
     1605c
     1606      ierr = NF_INQ_VARID (nid, "EMA_WORK2", nvarid)
     1607      IF (ierr.NE.NF_NOERR) THEN
     1608         PRINT*, "phyetat0: Le champ <EMA_WORK2> est absent"
     1609         PRINT*, "Depart legerement fausse. Mais je continue"
     1610         ema_work2=0.
     1611      ELSE
     1612#ifdef NC_DOUBLE
     1613         ierr = NF_GET_VAR_DOUBLE(nid, nvarid, ema_work2)
     1614#else
     1615         ierr = NF_GET_VAR_REAL(nid, nvarid, ema_work2)
     1616#endif
     1617         IF (ierr.NE.NF_NOERR) THEN
     1618            PRINT*, "phyetat0: Lecture echouee pour <EMA_WORK2>"
     1619            CALL abort
     1620         ENDIF
     1621           xmin = 1.0E+20
     1622           xmax = -1.0E+20
     1623           DO k = 1, klev
     1624           DO i = 1, klon
     1625              xmin = MIN(ema_work2(i,k),xmin)
     1626              xmax = MAX(ema_work2(i,k),xmax)
     1627           ENDDO
     1628           ENDDO
     1629           PRINT*,'ema_work2:', xmin, xmax
     1630      ENDIF
    15891631c
    15901632c Fermer le fichier:
     
    16251667      call Scatter( zmax0,zmax0_p)
    16261668      call Scatter( f0,f0_p)
     1669      call Scatter( ema_work1, ema_work1_p)
     1670      call Scatter( ema_work2, ema_work2_p)
    16271671      call Scatter( tsoil,tsoil_p)
    16281672      call Scatter( tslab,tslab_p)
  • LMDZ4/trunk/libf/phylmd/phyredem.F

    r927 r937  
    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, zmax0_p, f0_p)
     12     .           pbl_tke_p, zmax0_p, f0_p, ema_work1_p, ema_work2_p)
    1313
    1414      USE dimphy
     
    4040      REAL pbl_tke_p(klon,klev,nbsrf)
    4141      REAL zmax0_p(klon), f0_p(klon)
     42      REAL ema_work1_p(klon, klev), ema_work2_p(klon, klev)
    4243      REAL tsoil_p(klon,nsoilmx,nbsrf)
    4344      CHARACTER*6 ocean
     
    7576      REAL pbl_tke(klon_glo,klev,nbsrf)
    7677      REAL zmax0(klon_glo), f0(klon)
     78      REAL ema_work1(klon, klev), ema_work2(klon, klev)
    7779      REAL tsoil(klon_glo,nsoilmx,nbsrf)
    7880      REAL tslab(klon_glo), seaice(klon_glo)
     
    143145      call Gather( zmax0_p,zmax0)
    144146      call Gather( f0_p,f0)
     147      call Gather( ema_work1_p, ema_work1)
     148      call Gather( ema_work2_p, ema_work2)
    145149      call Gather( tsoil_p,tsoil)
    146150      call Gather( tslab_p,tslab)
  • LMDZ4/trunk/libf/phylmd/phys_state_var_mod.F90

    r927 r937  
    3030      REAL, ALLOCATABLE, SAVE :: pbl_tke(:,:,:) ! turb kinetic energy
    3131      REAL, ALLOCATABLE, SAVE :: zmax0(:), f0(:) !
    32 
     32      REAL, ALLOCATABLE, SAVE :: ema_work1(:,:), ema_work2(:,:)
    3333CONTAINS
    3434
     
    5858      ALLOCATE(pbl_tke(klon,klev+1,nbsrf))
    5959      ALLOCATE(zmax0(klon), f0(klon))
     60      ALLOCATE(ema_work1(klon,klev), ema_work2(klon,klev))
    6061
    6162END SUBROUTINE phys_state_var_init
     
    7576      deallocate( ratqs, pbl_tke )
    7677      deallocate( zmax0, f0 )
     78      deallocate( ema_work1, ema_work2 )
    7779
    7880END SUBROUTINE phys_state_var_end
  • LMDZ4/trunk/libf/phylmd/physiq.F

    r933 r937  
    702702c$OMP THREADPRIVATE(qcondc)
    703703cym      SAVE qcondc
    704       REAL,allocatable,save :: ema_work1(:, :), ema_work2(:, :)
    705 c$OMP THREADPRIVATE(ema_work1,ema_work2)
    706 cym      SAVE ema_work1, ema_work2
    707704      REAL wdn(klon), tdn(klon), qdn(klon)
    708705
     
    14301427      allocate( Ma(klon,klev) )
    14311428      allocate( qcondc(klon,klev)) 
    1432       allocate( ema_work1(klon, klev), ema_work2(klon, klev))
    14331429      allocate( wd(klon) )
    14341430      allocate( pfrac_impa(klon,klev))
     
    15121508        ratqs(:,:)=0.
    15131509        sollw(:)=0.
    1514         ema_work1(:,:)=0.
    1515         ema_work2(:,:)=0.
    15161510cym Attention pbase pas initialise dans concvl !!!!
    15171511        pbase(:)=0
     
    16401634     .       zmea,zstd,zsig,zgam,zthe,zpic,zval,rugoro,tabcntr0,
    16411635     .       t_ancien, q_ancien, ancien_ok, rnebcon, ratqs,clwcon,
    1642      .       pbl_tke, zmax0, f0)
     1636     .       pbl_tke, zmax0, f0, ema_work1, ema_work2)
    16431637
    16441638
     
    37593753     .      zmea,zstd,zsig,zgam,zthe,zpic,zval,rugoro,
    37603754     .      t_ancien, q_ancien, rnebcon, ratqs, clwcon,
    3761      .      pbl_tke, zmax0, f0)
     3755     .      pbl_tke, zmax0, f0, ema_work1, ema_work2)
    37623756         open(97,form="unformatted",file="finbin")
    37633757         write(97) u_seri,v_seri,t_seri,q_seri
Note: See TracChangeset for help on using the changeset viewer.