Ignore:
Timestamp:
Mar 8, 2011, 9:10:25 AM (14 years ago)
Author:
Laurent Fairhead
Message:

Merge of development branch LMDZ5V2.0-dev r1455:r1491 into the trunk.
Validation made locally: restart files are strictly equal between the HEAD of the trunk
and r1491 of LMDZ5V2.0-dev


Synchro de la branche de développement LMDZ5V2.0-dev r1455:r1491 et de la trunk
Validation faite en local: les fichiers restart sont équivalents entre la HEAD de la trunk
et la révision r1491 de LMDZ5V2.0-dev

Location:
LMDZ5/trunk
Files:
1 deleted
8 edited
5 copied

Legend:

Unmodified
Added
Removed
  • LMDZ5/trunk

  • LMDZ5/trunk/libf/phylmd/conf_phys.F90

    r1423 r1492  
    1313  subroutine conf_phys(ok_journe, ok_mensuel, ok_instan, ok_hf, &
    1414                       ok_LES,&
     15                       callstats,&
    1516                       solarlong0,seuil_inversion, &
    1617                       fact_cldcon, facttemps,ok_newmicro,iflag_radia,&
     
    6667  logical              :: ok_journe, ok_mensuel, ok_instan, ok_hf
    6768  logical              :: ok_LES
     69  LOGICAL              :: callstats
    6870  LOGICAL              :: ok_ade, ok_aie, aerosol_couple
    6971  INTEGER              :: flag_aerosol
     
    7981  logical,SAVE        :: ok_journe_omp, ok_mensuel_omp, ok_instan_omp, ok_hf_omp       
    8082  logical,SAVE        :: ok_LES_omp   
     83  LOGICAL,SAVE        :: callstats_omp
    8184  LOGICAL,SAVE        :: ok_ade_omp, ok_aie_omp, aerosol_couple_omp
    8285  INTEGER, SAVE       :: flag_aerosol_omp
     
    14181421  ok_LES_omp = .false.                                             
    14191422  call getin('OK_LES', ok_LES_omp)                                 
     1423
     1424!Config Key  = callstats                                               
     1425!Config Desc = Pour des sorties callstats                                 
     1426!Config Def  = .false.                                             
     1427!Config Help = Pour creer le fichier stats contenant les sorties 
     1428!              stats                                                 
     1429!                                                                   
     1430  callstats_omp = .false.                                             
     1431  call getin('callstats', callstats_omp)                                 
    14201432!
    14211433!Config Key  = ecrit_LES
     
    15811593    ok_hines = ok_hines_omp
    15821594    ok_LES = ok_LES_omp
     1595    callstats = callstats_omp
    15831596    ecrit_LES = ecrit_LES_omp
    15841597    carbon_cycle_tr = carbon_cycle_tr_omp
  • LMDZ5/trunk/libf/phylmd/orografi_strato.F

    r1403 r1492  
    20042004
    20052005      DO 110 JK=1,NLEV
    2006       ZPM1R=pplay_glo(klon_glo/2,jk)/paprs_glo(klon_glo/2,1)
     2006      ZPM1R=pplay_glo(klon_glo/2,jk)/paprs_glo(klon_glo/2+1,1)
    20072007      IF(ZPM1R.GE.ZSIGT)THEN
    20082008         nktopg=JK
    20092009      ENDIF
    2010       ZPM1R=pplay_glo(klon_glo/2,jk)/paprs_glo(klon_glo/2,1)
     2010      ZPM1R=pplay_glo(klon_glo/2,jk)/paprs_glo(klon_glo/2+1,1)
    20112011      IF(ZPM1R.GE.ZTOP)THEN
    20122012         nstra=JK
  • LMDZ5/trunk/libf/phylmd/phys_output_mod.F90

    r1424 r1492  
    427427  type(ctrl_out),save :: o_pres         = ctrl_out((/ 2, 3, 10, 10, 1 /),'pres')
    428428  type(ctrl_out),save :: o_paprs        = ctrl_out((/ 2, 3, 10, 10, 1 /),'paprs')
     429  type(ctrl_out),save :: o_mass        = ctrl_out((/ 2, 3, 10, 10, 1 /),'mass')
     430
    429431  type(ctrl_out),save :: o_rneb         = ctrl_out((/ 2, 5, 10, 10, 1 /),'rneb')
    430432  type(ctrl_out),save :: o_rnebcon      = ctrl_out((/ 2, 5, 10, 10, 1 /),'rnebcon')
     
    10571059! Couplage conv-CL
    10581060 IF (iflag_con.GE.3) THEN
    1059     IF (iflag_coupl.EQ.1) THEN
     1061    IF (iflag_coupl>=1) THEN
    10601062 CALL histdef2d(iff,o_ale_bl%flag,o_ale_bl%name, "ALE BL", "m2/s2")
    10611063 CALL histdef2d(iff,o_alp_bl%flag,o_alp_bl%name, "ALP BL", "m2/s2")
     
    11081110 CALL histdef3d(iff,o_pres%flag,o_pres%name, "Air pressure", "Pa" )
    11091111 CALL histdef3d(iff,o_paprs%flag,o_paprs%name, "Air pressure Inter-Couches", "Pa" )
     1112 CALL histdef3d(iff,o_mass%flag,o_mass%name, "Masse Couches", "kg/m2" )
    11101113 CALL histdef3d(iff,o_rneb%flag,o_rneb%name, "Cloud fraction", "-")
    11111114 CALL histdef3d(iff,o_rnebcon%flag,o_rnebcon%name, "Convective Cloud Fraction", "-")
  • LMDZ5/trunk/libf/phylmd/phys_output_write.h

    r1403 r1492  
    104104     s                   o_psol%name,itau_w,zx_tmp_fi2d)
    105105       ENDIF
     106
     107       IF (o_mass%flag(iff)<=lev_files(iff)) THEN
     108      CALL histwrite_phy(nid_files(iff),o_mass%name,itau_w,zmasse)
     109        ENDIF
     110
    106111
    107112       IF (o_qsurf%flag(iff)<=lev_files(iff)) THEN
     
    691696! Couplage convection-couche limite
    692697      IF (iflag_con.GE.3) THEN
    693       IF (iflag_coupl.EQ.1) THEN
     698      IF (iflag_coupl>=1) THEN
    694699       IF (o_ale_bl%flag(iff)<=lev_files(iff)) THEN
    695700       CALL histwrite_phy(nid_files(iff),o_ale_bl%name,itau_w,ale_bl)
     
    698703       CALL histwrite_phy(nid_files(iff),o_alp_bl%name,itau_w,alp_bl)
    699704       ENDIF
    700       ENDIF !iflag_coupl.EQ.1
     705      ENDIF !iflag_coupl>=1
    701706      ENDIF !(iflag_con.GE.3)
    702707
  • LMDZ5/trunk/libf/phylmd/physiq.F

    r1479 r1492  
    158158      save ok_LES                           
    159159c$OMP THREADPRIVATE(ok_LES)                 
     160c
     161      LOGICAL callstats ! sortir le fichier stats
     162      save callstats                           
     163c$OMP THREADPRIVATE(callstats)                 
    160164c
    161165      LOGICAL ok_region ! sortir le fichier regional
     
    11501154!     and 360
    11511155
     1156      INTEGER ierr
    11521157#include "YOMCST.h"
    11531158#include "YOETHF.h"
     
    12221227     .     ok_instan, ok_hf,
    12231228     .     ok_LES,
     1229     .     callstats,
    12241230     .     solarlong0,seuil_inversion,
    12251231     .     fact_cldcon, facttemps,ok_newmicro,iflag_radia,
     
    24592465      endif
    24602466! ----------------------------------------------------------------------
     2467!IM/FH: 2011/02/23
     2468! Couplage Thermiques/Emanuel seulement si T<0
     2469      if (iflag_coupl==2) then
     2470        print*,'Couplage Thermiques/Emanuel seulement si T<0'
     2471        do i=1,klon
     2472           if (t_seri(i,lmax_th(i))>273.) then
     2473              Ale_bl(i)=0.
     2474           endif
     2475        enddo
     2476      endif
    24612477
    24622478         endif
     
    28342850! de la convection profonde.
    28352851
     2852!IM/FH: 2011/02/23
     2853! definition des points sur lesquels ls thermiques sont actifs
    28362854         if (prt_level>9)write(*,*)'TEST SCHEMA DE NUAGES '
     2855         ptconvth(:,:)=fm_therm(:,:)>0.
    28372856         do k=1,klev
    28382857            do i=1,klon
     
    36953714c====================================================================
    36963715c
    3697      
     3716
     3717c        -----------------------------------------------------------------
     3718c        WSTATS: Saving statistics
     3719c        -----------------------------------------------------------------
     3720c        ("stats" stores and accumulates 8 key variables in file "stats.nc"
     3721c        which can later be used to make the statistic files of the run:
     3722c        "stats")          only possible in 3D runs !
     3723
     3724         
     3725         IF (callstats) THEN
     3726
     3727           call wstats(klon,o_psol%name,"Surface pressure","Pa"
     3728     &                 ,2,paprs(:,1))
     3729           call wstats(klon,o_tsol%name,"Surface temperature","K",
     3730     &                 2,zxtsol)
     3731           zx_tmp_fi2d(:) = rain_fall(:) + snow_fall(:)
     3732           call wstats(klon,o_precip%name,"Precip Totale liq+sol",
     3733     &                 "kg/(s*m2)",2,zx_tmp_fi2d)
     3734           zx_tmp_fi2d(:) = rain_lsc(:) + snow_lsc(:)
     3735           call wstats(klon,o_plul%name,"Large-scale Precip",
     3736     &                 "kg/(s*m2)",2,zx_tmp_fi2d)
     3737           zx_tmp_fi2d(:) = rain_con(:) + snow_con(:)
     3738           call wstats(klon,o_pluc%name,"Convective Precip",
     3739     &                 "kg/(s*m2)",2,zx_tmp_fi2d)
     3740           call wstats(klon,o_sols%name,"Solar rad. at surf.",
     3741     &                 "W/m2",2,solsw)
     3742           call wstats(klon,o_soll%name,"IR rad. at surf.",
     3743     &                 "W/m2",2,sollw)
     3744          zx_tmp_fi2d(:) = topsw(:)-toplw(:)
     3745          call wstats(klon,o_nettop%name,"Net dn radiatif flux at TOA",
     3746     &                 "W/m2",2,zx_tmp_fi2d)
     3747
     3748
     3749
     3750           call wstats(klon,o_temp%name,"Air temperature","K",
     3751     &                 3,t_seri)
     3752           call wstats(klon,o_vitu%name,"Zonal wind","m.s-1",
     3753     &                 3,u_seri)
     3754           call wstats(klon,o_vitv%name,"Meridional wind",
     3755     &                "m.s-1",3,v_seri)
     3756           call wstats(klon,o_vitw%name,"Vertical wind",
     3757     &                "m.s-1",3,omega)
     3758           call wstats(klon,o_ovap%name,"Specific humidity", "kg/kg",
     3759     &                 3,q_seri)
     3760 
     3761
     3762
     3763           IF(lafin) THEN
     3764             write (*,*) "Writing stats..."
     3765             call mkstats(ierr)
     3766           ENDIF
     3767
     3768         ENDIF !if callstats
     3769     
    36983770
    36993771      IF (lafin) THEN
  • LMDZ5/trunk/libf/phylmd/readaerosol.F90

    r1403 r1492  
    77CONTAINS
    88
    9 SUBROUTINE readaerosol(name_aero, type, iyr_in, klev_src, pt_ap, pt_b, pt_out, psurf, load)
     9SUBROUTINE readaerosol(name_aero, type, filename, iyr_in, klev_src, pt_ap, pt_b, pt_out, psurf, load)
    1010
    1111!****************************************************************************************
     
    2727  ! Input arguments
    2828  CHARACTER(len=7), INTENT(IN) :: name_aero
    29   CHARACTER(len=*), INTENT(IN) :: type  ! correspond to aer_type in clesphys.h
     29  CHARACTER(len=*), INTENT(IN) :: type  ! actuel, annuel, scenario or preind
     30  CHARACTER(len=8), INTENT(IN) :: filename
    3031  INTEGER, INTENT(IN)          :: iyr_in
    3132
     
    5859     ! get_aero_fromfile returns pt_out allocated and initialized with data for 12 month
    5960     ! pt_out has dimensions (klon, klev_src, 12)
    60      CALL get_aero_fromfile(name_aero, cyear, klev_src, pt_ap, pt_b, p0, pt_out, psurf, load)
     61     CALL get_aero_fromfile(name_aero, cyear, filename, klev_src, pt_ap, pt_b, p0, pt_out, psurf, load)
    6162     
    6263
     
    6768     ! get_aero_fromfile returns pt_out allocated and initialized with data for 12 month
    6869     ! pt_out has dimensions (klon, klev_src, 12)
    69      CALL get_aero_fromfile(name_aero, cyear, klev_src, pt_ap, pt_b, p0, pt_out, psurf, load)
     70     CALL get_aero_fromfile(name_aero, cyear, filename, klev_src, pt_ap, pt_b, p0, pt_out, psurf, load)
    7071     
    7172  ELSE IF (type == 'annuel') THEN
     
    7677     ! get_aero_fromfile returns pt_out allocated and initialized with data for nbr_tsteps month
    7778     ! pt_out has dimensions (klon, klev_src, 12)
    78      CALL get_aero_fromfile(name_aero, cyear, klev_src, pt_ap, pt_b, p0, pt_out, psurf, load)
     79     CALL get_aero_fromfile(name_aero, cyear, filename, klev_src, pt_ap, pt_b, p0, pt_out, psurf, load)
    7980     
    8081  ELSE IF (type == 'scenario') THEN
     
    8687        ! get_aero_fromfile returns pt_out allocated and initialized with data for 12 month
    8788        ! pt_out has dimensions (klon, klev_src, 12)
    88         CALL get_aero_fromfile(name_aero, cyear, klev_src, pt_ap, pt_b, p0, pt_out, psurf, load)
     89        CALL get_aero_fromfile(name_aero, cyear, filename, klev_src, pt_ap, pt_b, p0, pt_out, psurf, load)
    8990       
    9091     ELSE IF (iyr_in .GE. 2100) THEN
     
    9394        ! get_aero_fromfile returns pt_out allocated and initialized with data for 12 month
    9495        ! pt_out has dimensions (klon, klev_src, 12)
    95         CALL get_aero_fromfile(name_aero, cyear, klev_src, pt_ap, pt_b, p0, pt_out, psurf, load)
     96        CALL get_aero_fromfile(name_aero, cyear, filename, klev_src, pt_ap, pt_b, p0, pt_out, psurf, load)
    9697       
    9798     ELSE
     
    113114        ! get_aero_fromfile returns pt_out allocated and initialized with data for 12 month
    114115        ! pt_out has dimensions (klon, klev_src, 12)
    115         CALL get_aero_fromfile(name_aero, cyear, klev_src, pt_ap, pt_b, p0, pt_out, psurf, load)
     116        CALL get_aero_fromfile(name_aero, cyear, filename, klev_src, pt_ap, pt_b, p0, pt_out, psurf, load)
    116117       
    117118        ! If to read two decades:
     
    125126           ! get_aero_fromfile returns pt_2 allocated and initialized with data for 12 month
    126127           ! pt_2 has dimensions (klon, klev_src, 12)
    127            CALL get_aero_fromfile(name_aero, cyear, klev_src2, pt_ap, pt_b, p0, pt_2, psurf2, load2)
     128           CALL get_aero_fromfile(name_aero, cyear, filename, klev_src2, pt_ap, pt_b, p0, pt_2, psurf2, load2)
    128129           ! Test for same number of vertical levels
    129130           IF (klev_src /= klev_src2) THEN
     
    160161
    161162  ELSE
    162      WRITE(lunout,*)'This option is not implemented : aer_type = ', type
     163     WRITE(lunout,*)'This option is not implemented : aer_type = ', type,' name_aero=',name_aero
    163164     CALL abort_gcm('readaerosol','Error : aer_type parameter not accepted',1)
    164165  END IF ! type
     
    168169
    169170
    170   SUBROUTINE get_aero_fromfile(varname, cyr, klev_src, pt_ap, pt_b, p0, pt_year, psurf_out, load_out)
     171  SUBROUTINE get_aero_fromfile(varname, cyr, filename, klev_src, pt_ap, pt_b, p0, pt_year, psurf_out, load_out)
    171172!****************************************************************************************
    172173! Read 12 month aerosol from file and distribute to local process on physical grid.
     
    200201    CHARACTER(len=7), INTENT(IN)          :: varname
    201202    CHARACTER(len=4), INTENT(IN)          :: cyr
     203    CHARACTER(len=8), INTENT(IN)          :: filename
    202204
    203205! Output arguments
     
    213215! Local variables
    214216    CHARACTER(len=30)     :: fname
    215     CHARACTER(len=8)      :: filename='aerosols'
    216217    CHARACTER(len=30)     :: cvar
    217218    INTEGER               :: ncid, dimid, varid
     
    242243! 1) Open file
    243244!****************************************************************************************
    244        fname = filename//cyr//'.nc'
     245! Add suffix to filename
     246       fname = trim(filename)//cyr//'.nc'
    245247 
    246        WRITE(lunout,*) 'reading ', TRIM(fname)
     248       WRITE(lunout,*) 'reading variable ',TRIM(varname),' in file ', TRIM(fname)
    247249       CALL check_err( nf90_open(TRIM(fname), NF90_NOWRITE, ncid) )
    248250
     
    283285          CALL abort_gcm('get_aero_fromfile', 'latitudes do not correspond between file and model',1)
    284286       END IF
    285 
    286 ! 1.5) Check number of month in file opened
    287 !
    288 !**************************************************************************************************
    289        ierr = nf90_inq_dimid(ncid, 'TIME',dimid)
    290        CALL check_err( nf90_inquire_dimension(ncid, dimid, len = nbr_tsteps) )
    291 !       IF (nbr_tsteps /= 12 .AND. nbr_tsteps /= 14) THEN
    292        IF (nbr_tsteps /= 12 ) THEN
    293          CALL abort_gcm('get_aero_fromfile', 'not the right number of months in aerosol file read (should be 12 for the moment)',1)
    294        ENDIF
    295287
    296288
     
    335327
    336328       IF (new_file) THEN
     329! ++) Check number of month in file opened
     330!**************************************************************************************************
     331       ierr = nf90_inq_dimid(ncid, 'TIME',dimid)
     332       CALL check_err( nf90_inquire_dimension(ncid, dimid, len = nbr_tsteps) )
     333!       IF (nbr_tsteps /= 12 .AND. nbr_tsteps /= 14) THEN
     334       IF (nbr_tsteps /= 12 ) THEN
     335         CALL abort_gcm('get_aero_fromfile', 'not the right number of months in aerosol file read (should be 12 for the moment)',1)
     336       ENDIF
    337337
    338338! ++) Read the aerosol concentration month by month and concatenate to total variable varyear
  • LMDZ5/trunk/libf/phylmd/readaerosol_interp.F90

    r1403 r1492  
    9292  LOGICAL,SAVE       :: debug=.FALSE.! Debugging in this subroutine
    9393!$OMP THREADPRIVATE(vert_interp, debug)
     94  CHARACTER(len=8)      :: type
     95  CHARACTER(len=8)      :: filename
    9496
    9597
     
    173175     ! Reading values corresponding to the closest year taking into count the choice of aer_type.
    174176     ! For aer_type=scenario interpolation between 2 data sets is done in readaerosol.
    175      CALL readaerosol(name_aero(id_aero), aer_type, iyr, klev_src, pt_ap, pt_b, pt_tmp, &
     177     ! If aer_type=mix1 or mix2, the run type and file name depends on the aerosol.
     178     IF (aer_type=='preind' .OR. aer_type=='actuel' .OR. aer_type=='annuel' .OR. aer_type=='scenario') THEN
     179        ! Standard case
     180        filename='aerosols'
     181        type=aer_type
     182     ELSE IF (aer_type == 'mix1') THEN
     183        ! Special case using a mix of decenal sulfate file and annual aerosols(all aerosols except sulfate)
     184        IF (name_aero(id_aero) == 'SO4') THEN
     185           filename='so4.run '
     186           type='scenario'
     187        ELSE
     188           filename='aerosols'
     189           type='annuel'
     190        END IF
     191     ELSE  IF (aer_type == 'mix2') THEN
     192        ! Special case using a mix of decenal sulfate file and natrual aerosols
     193        IF (name_aero(id_aero) == 'SO4') THEN
     194           filename='so4.run '
     195           type='scenario'
     196        ELSE
     197           filename='aerosols'
     198           type='preind'
     199        END IF
     200     ELSE
     201        CALL abort_gcm('readaerosol_interp', 'this aer_type not supported',1)
     202     END IF
     203
     204     CALL readaerosol(name_aero(id_aero), type, filename, iyr, klev_src, pt_ap, pt_b, pt_tmp, &
    176205          psurf_year(:,:,id_aero), load_year(:,:,id_aero))
    177206     IF (.NOT. ALLOCATED(var_year)) THEN
     
    182211
    183212     ! Reading values corresponding to the preindustrial concentrations.
    184      CALL readaerosol(name_aero(id_aero), 'preind', iyr, pi_klev_src, pt_ap, pt_b, pt_tmp, &
     213     type='preind'
     214     CALL readaerosol(name_aero(id_aero), type, filename, iyr, pi_klev_src, pt_ap, pt_b, pt_tmp, &
    185215          pi_psurf_year(:,:,id_aero), pi_load_year(:,:,id_aero))
    186216
Note: See TracChangeset for help on using the changeset viewer.