Changeset 1492


Ignore:
Timestamp:
Mar 8, 2011, 9:10:25 AM (13 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:
9 deleted
25 edited
18 copied

Legend:

Unmodified
Added
Removed
  • LMDZ5/trunk

  • LMDZ5/trunk/arch/arch-PW6_VARGAS.fcm

    r1477 r1492  
    55%FPP_FLAGS           -P -I/usr/local/pub/FFTW/3.2/include
    66%FPP_DEF             NC_DOUBLE BLAS SGEMV=DGEMV SGEMM=DGEMM FFT_FFTW
    7 %BASE_FFLAGS         -qautodbl=dbl4 -qxlf90=autodealloc -qmaxmem=-1 -qzerosize
     7%BASE_FFLAGS         -qautodbl=dbl4 -qxlf90=autodealloc -qmaxmem=-1 -qzerosize -I/usr/local/pub/FFTW/3.2/include
    88%PROD_FFLAGS         -O3
    99%DEV_FFLAGS          -O2 -qfullpath -qinitauto=7FBFFFFF -qfloat=nans -qflttrap=overflow:zerodivide:invalid:enable -qsigtrap
  • LMDZ5/trunk/create_make_gcm

    r1403 r1492  
    11#!/bin/sh
    22#
    3 # $Header$
     3# $Id$
    44#
    55#set -xv
     
    5959echo '# Les differentes librairies pour l"edition des liens:'
    6060echo
    61 if ( [ "$XNEC" = '1' ] || [ "$X6NEC" = '1' ] || [ "$X8BRODIE" = '1' ] ) ; then
    62   echo 'dyn3d      = $(LIBO)/libsxdyn3d.a $(LIBO)/libsx$(FILTRE).a'
    63   echo 'dyn3dpar     = $(LIBO)/libsxdyn3dpar.a $(LIBO)/libsx$(FILTRE).a'
    64   echo 'dyn2d      = $(LIBO)/libsxdyn2d.a'
    65   echo 'dyn1d      = $(LIBO)/libsxdyn1d.a'
    66   echo 'L_DYN      = -lsxdyn$(DIM)d$(FLAG_PARA)'
    67   echo 'L_FILTRE   = -lsx$(FILTRE)'
    68   echo 'L_PHY = -lsxphy$(PHYS) '
    69   echo 'L_BIBIO    = -lsxbibio'
    70   echo 'L_ADJNT    ='
    71   echo 'L_COSP     = -lsxcosp'
    72 else
    73   echo 'dyn3d            = $(LIBO)/libdyn3d.a $(LIBO)/lib$(FILTRE).a'
    74   echo 'dyn3dpar      = $(LIBO)/libdyn3dpar.a $(LIBO)/lib$(FILTRE).a'
    75   echo 'dyn2d            = $(LIBO)/libdyn2d.a'
    76   echo 'dyn1d            = $(LIBO)/libdyn1d.a'
    77   echo 'L_DYN      = -ldyn$(DIM)d$(FLAG_PARA)'
    78   echo 'L_FILTRE   = -l$(FILTRE)'
    79   echo 'L_PHY = -lphy$(PHYS) '
    80   echo 'L_BIBIO    = -lbibio'
    81   echo 'L_ADJNT    ='
    82   echo 'L_COSP     = -lcosp'
    83 fi
     61echo 'dyn3d            = $(LIBO)/libdyn3d.a $(LIBO)/lib$(FILTRE).a'
     62echo 'dyn3dpar      = $(LIBO)/libdyn3dpar.a $(LIBO)/lib$(FILTRE).a'
     63echo 'dyn2d            = $(LIBO)/libdyn2d.a'
     64echo 'dyn1d            = $(LIBO)/libdyn1d.a'
     65echo 'L_DYN      = -ldyn$(DIM)d$(FLAG_PARA)'
     66echo 'L_FILTRE   = -l$(FILTRE)'
     67echo 'L_PHY = -lphy$(PHYS) '
     68echo 'L_BIBIO    = -lbibio'
     69echo 'L_ADJNT    ='
     70echo 'L_COSP     = -lcosp'
    8471
    8572echo
     
    219206         done
    220207         echo $str1
     208         # Compile in LIBO directory; and before compiling, remove
     209         # object from library
     210         echo ' cd $(LIBO); \'
     211         echo ' $(AR) d $(LIBO)/lib'$diri'.a '$fili'.o ; \'
    221212         if [ "$F90" -eq '0' ] ; then
    222            echo '       cd $(LOCAL_DIR); \'
     213         ## Fixed Form Fortran 77
    223214           echo '       $(COMPILE) $(LIBF)/'$diri'/'$trufile' ; \'
    224215         else
    225            echo '       cd $(LOCAL_DIR); \'
     216         ## Fortran 90
    226217           if [ -f $fili.F90 ] ; then
    227               echo '    $(COMPTRU90) $(LIBF)/'$diri'/'$trufile' ; \'
     218              ## Free Form
     219              echo '    $(COMPTRU90) $(LIBF)/'$diri'/'$trufile' ; \'
    228220           else
    229221              echo '    $(COMPILE90) $(LIBF)/'$diri'/'$trufile' ; \'
    230222           fi
    231            MODU=0; egrep -i '^ *module ' $trufile> /dev/null 2>&1 && MODU=1
    232             if [ "$MODU" -eq '1' -a "$CRAY" != '1' ] ; then
    233               if [ "$os" = 'UNIX_System_V' ] ; then
    234                 echo '  cp $(MOD_LOC_DIR)/*.$(MOD_SUFFIX) $(LIBO)/ ; \'
    235               else
    236                 echo '  mv $(MOD_LOC_DIR)/'$fili'.$(MOD_SUFFIX) $(LIBO)/'$fili'.$(MOD_SUFFIX) ; \'
    237 #                echo ' if [ "$(MOD_LOC_DIR)" ne "$(LIBO)" ] ; then mv $(MOD_LOC_DIR)/'*'.$(MOD_SUFFIX) $(LIBO) ; fi ; \'
    238               fi
    239             fi
    240223         fi
    241          if ( [ "$XNEC" -eq '1' ] || [ "$X6NEC" = '1' ] || [ "$X8BRODIE" = '1' ] ) ; then
    242            echo '       sxar r $(LIBO)/libsx'$diri'.a '$fili'.o ; \'
    243          fi
     224         # Put generated object in library
    244225         echo ' $(AR) r $(LIBO)/lib'$diri'.a '$fili'.o ; $(RM) '$fili'.o ; \'
    245226         echo ' cd $(GCM)'
  • LMDZ5/trunk/libf/dyn3d/ce0l.F90

    r1425 r1492  
    9191  END IF
    9292
     93  IF (grilles_gcm_netcdf) THEN
     94     WRITE(lunout,'(//)')
     95     WRITE(lunout,*) '  ***************************  '
     96     WRITE(lunout,*) '  ***  grilles_gcm_netcdf ***  '
     97     WRITE(lunout,*) '  ***************************  '
     98     WRITE(lunout,'(//)')
     99     CALL grilles_gcm_netcdf_sub()
     100  END IF
    93101#endif
    94102! of #ifndef CPP_EARTH #else
  • LMDZ5/trunk/libf/dyn3d/comdissipn.h

    r524 r1492  
    22! $Header$
    33!
    4 c-----------------------------------------------------------------------
    5 c INCLUDE comdissipn.h
     4!  Attention : ce fichier include est compatible format fixe/format libre
     5!                 veillez à n'utiliser que des ! pour les commentaires
     6!                 et à bien positionner les & des lignes de continuation
     7!                 (les placer en colonne 6 et en colonne 73)
     8!-----------------------------------------------------------------------
     9! INCLUDE comdissipn.h
    610
    711      REAL  tetaudiv, tetaurot, tetah, cdivu, crot, cdivh
    8 c
    9       COMMON/comdissipn/ tetaudiv(llm),tetaurot(llm),tetah(llm)   ,
    10      1                        cdivu,      crot,         cdivh
     12!
     13      COMMON/comdissipn/ tetaudiv(llm),tetaurot(llm),tetah(llm)   ,     &
     14     &                        cdivu,      crot,         cdivh
    1115
    12 c
    13 c    Les parametres de ce common proviennent des calculs effectues dans
    14 c             Inidissip  .
    15 c
    16 c-----------------------------------------------------------------------
     16!
     17!    Les parametres de ce common proviennent des calculs effectues dans
     18!             Inidissip  .
     19!
     20!-----------------------------------------------------------------------
  • LMDZ5/trunk/libf/dyn3d/conf_gcm.F

    r1418 r1492  
    841841      ok_etat0 = .TRUE.
    842842      CALL getin('ok_etat0',ok_etat0)
     843
     844!Config  Key  = grilles_gcm_netcdf
     845!Config  Desc = creation de fichier grilles_gcm.nc dans create_etat0_limit
     846!Config  Def  = n
     847      grilles_gcm_netcdf = .FALSE.
     848      CALL getin('grilles_gcm_netcdf',grilles_gcm_netcdf)
    843849
    844850      write(lunout,*)' #########################################'
     
    887893      write(lunout,*)' ok_limit = ', ok_limit
    888894      write(lunout,*)' ok_etat0 = ', ok_etat0
     895      write(lunout,*)' grilles_gcm_netcdf = ', grilles_gcm_netcdf
    889896c
    890897      RETURN
  • LMDZ5/trunk/libf/dyn3d/etat0_netcdf.F90

    r1425 r1492  
    9898  REAL    :: dummy
    9999  LOGICAL :: ok_newmicro, ok_journe, ok_mensuel, ok_instan, ok_hf
    100   LOGICAL :: ok_LES, ok_ade, ok_aie, aerosol_couple, new_aod
     100  LOGICAL :: ok_LES, ok_ade, ok_aie, aerosol_couple, new_aod, callstats
    101101  INTEGER :: iflag_radia, flag_aerosol
    102102  REAL    :: bl95_b0, bl95_b1, fact_cldcon, facttemps, ratqsbas, ratqshaut
     
    130130!--- CONSTRUCT A GRID
    131131  CALL conf_phys(  ok_journe, ok_mensuel, ok_instan, ok_hf, ok_LES,     &
     132                   callstats,                                           &
    132133                   solarlong0,seuil_inversion,                          &
    133134                   fact_cldcon, facttemps,ok_newmicro,iflag_radia,      &
  • LMDZ5/trunk/libf/dyn3d/logic.h

    r1319 r1492  
    1010     &  statcl,conser,apdiss,apdelq,saison,ecripar,fxyhypb,ysinus       &
    1111     &  ,read_start,ok_guide,ok_strato,ok_gradsfile                     &
    12      &  ,ok_limit,ok_etat0
     12     &  ,ok_limit,ok_etat0,grilles_gcm_netcdf
    1313
    1414      LOGICAL purmats,forward,leapf,apphys,statcl,conser,               &
    1515     & apdiss,apdelq,saison,ecripar,fxyhypb,ysinus                      &
    1616     &  ,read_start,ok_guide,ok_strato,ok_gradsfile                     &
    17      &  ,ok_limit,ok_etat0
     17     &  ,ok_limit,ok_etat0,grilles_gcm_netcdf
    1818
    1919      INTEGER iflag_phys
  • LMDZ5/trunk/libf/dyn3dpar/abort_gcm.F

    r1425 r1492  
    4545      if (ierr .eq. 0) then
    4646        write(lunout,*) 'Everything is cool'
    47         stop
    4847      else
    4948        write(lunout,*) 'Houston, we have a problem ', ierr
  • LMDZ5/trunk/libf/dyn3dpar/ce0l.F90

    r1425 r1492  
    2222  USE mod_const_mpi
    2323  USE infotrac
     24  USE parallel, ONLY: finalize_parallel
    2425
    2526#ifdef CPP_IOIPSL
     
    5556       CALL abort_gcm('ce0l','In parallel mode,                         &
    5657 &                 ce0l must be called only                             &
    57  &                 for 1 process and 1 task')
     58 &                 for 1 process and 1 task',1)
    5859  ENDIF
    5960
     
    101102  END IF
    102103
     104  IF (grilles_gcm_netcdf) THEN
     105     WRITE(lunout,'(//)')
     106     WRITE(lunout,*) '  ***************************  '
     107     WRITE(lunout,*) '  ***  grilles_gcm_netcdf ***  '
     108     WRITE(lunout,*) '  ***************************  '
     109     WRITE(lunout,'(//)')
     110     CALL grilles_gcm_netcdf_sub()
     111  END IF
     112 
     113!$OMP MASTER
     114  CALL finalize_parallel
     115!$OMP END MASTER
     116
    103117#endif
    104118! of #ifndef CPP_EARTH #else
  • LMDZ5/trunk/libf/dyn3dpar/comdissipn.h

    r774 r1492  
    22! $Header$
    33!
    4 c-----------------------------------------------------------------------
    5 c INCLUDE comdissipn.h
     4!  Attention : ce fichier include est compatible format fixe/format libre
     5!                 veillez à n'utiliser que des ! pour les commentaires
     6!                 et à bien positionner les & des lignes de continuation
     7!                 (les placer en colonne 6 et en colonne 73)
     8!-----------------------------------------------------------------------
     9! INCLUDE comdissipn.h
    610
    711      REAL  tetaudiv, tetaurot, tetah, cdivu, crot, cdivh
    8 c
    9       COMMON/comdissipn/ tetaudiv(llm),tetaurot(llm),tetah(llm)   ,
    10      1                        cdivu,      crot,         cdivh
     12!
     13      COMMON/comdissipn/ tetaudiv(llm),tetaurot(llm),tetah(llm)   ,     &
     14     &                        cdivu,      crot,         cdivh
    1115
    12 c
    13 c    Les parametres de ce common proviennent des calculs effectues dans
    14 c             Inidissip  .
    15 c
    16 c-----------------------------------------------------------------------
     16!
     17!    Les parametres de ce common proviennent des calculs effectues dans
     18!             Inidissip  .
     19!
     20!-----------------------------------------------------------------------
  • LMDZ5/trunk/libf/dyn3dpar/conf_gcm.F

    r1454 r1492  
    888888      ok_etat0 = .TRUE.
    889889      CALL getin('ok_etat0',ok_etat0)
     890
     891!Config  Key  = grilles_gcm_netcdf
     892!Config  Desc = creation de fichier grilles_gcm.nc dans create_etat0_limit
     893!Config  Def  = n
     894      grilles_gcm_netcdf = .FALSE.
     895      CALL getin('grilles_gcm_netcdf',grilles_gcm_netcdf)
    890896
    891897      write(lunout,*)' #########################################'
     
    937943      write(lunout,*)' ok_limit = ', ok_limit
    938944      write(lunout,*)' ok_etat0 = ', ok_etat0
     945      write(lunout,*)' grilles_gcm_netcdf = ', grilles_gcm_netcdf
    939946c
    940947      RETURN
  • LMDZ5/trunk/libf/dyn3dpar/etat0_netcdf.F90

    r1425 r1492  
    9898  REAL    :: dummy
    9999  LOGICAL :: ok_newmicro, ok_journe, ok_mensuel, ok_instan, ok_hf
    100   LOGICAL :: ok_LES, ok_ade, ok_aie, aerosol_couple, new_aod
     100  LOGICAL :: ok_LES, ok_ade, ok_aie, aerosol_couple, new_aod, callstats
    101101  INTEGER :: iflag_radia, flag_aerosol
    102102  REAL    :: bl95_b0, bl95_b1, fact_cldcon, facttemps, ratqsbas, ratqshaut
     
    130130!--- CONSTRUCT A GRID
    131131  CALL conf_phys(  ok_journe, ok_mensuel, ok_instan, ok_hf, ok_LES,     &
     132                   callstats,                                           &
    132133                   solarlong0,seuil_inversion,                          &
    133134                   fact_cldcon, facttemps,ok_newmicro,iflag_radia,      &
  • LMDZ5/trunk/libf/dyn3dpar/friction_p.F

    r1454 r1492  
    3434
    3535! arguments:
    36       REAL,INTENT(out) :: ucov( iip1,jjp1,llm )
    37       REAL,INTENT(out) :: vcov( iip1,jjm,llm )
     36      REAL,INTENT(inout) :: ucov( iip1,jjp1,llm )
     37      REAL,INTENT(inout) :: vcov( iip1,jjm,llm )
    3838      REAL,INTENT(in) :: pdt ! time step
    3939
  • LMDZ5/trunk/libf/dyn3dpar/leapfrog_p.F

    r1454 r1492  
    996996          enddo
    997997!$OMP END DO
    998 !$OMP SINGLE
     998!$OMP MASTER
    999999          dpfi(ijb:ije)=0
    1000 !$OMP END SINGLE
     1000!$OMP END MASTER
    10011001          ijb=ij_begin
    10021002          ije=ij_end
  • LMDZ5/trunk/libf/dyn3dpar/logic.h

    r1319 r1492  
    1010     &  statcl,conser,apdiss,apdelq,saison,ecripar,fxyhypb,ysinus       &
    1111     &  ,read_start,ok_guide,ok_strato,ok_gradsfile                     &
    12      &  ,ok_limit,ok_etat0
     12     &  ,ok_limit,ok_etat0,grilles_gcm_netcdf
    1313
    1414      LOGICAL purmats,forward,leapf,apphys,statcl,conser,               &
    1515     & apdiss,apdelq,saison,ecripar,fxyhypb,ysinus                      &
    1616     &  ,read_start,ok_guide,ok_strato,ok_gradsfile                     &
    17      &  ,ok_limit,ok_etat0
     17     &  ,ok_limit,ok_etat0,grilles_gcm_netcdf
    1818
    1919      INTEGER iflag_phys
  • LMDZ5/trunk/libf/dyn3dpar/parallel.F90

    r1279 r1492  
    55  USE mod_const_mpi
    66   
    7     LOGICAL,SAVE :: using_mpi
     7    LOGICAL,SAVE :: using_mpi=.TRUE.
    88    LOGICAL,SAVE :: using_omp
    99   
     
    208208      integer :: ierr
    209209      integer :: i
    210       deallocate(jj_begin_para)
    211       deallocate(jj_end_para)
    212       deallocate(jj_nb_para)
     210
     211      if (allocated(jj_begin_para)) deallocate(jj_begin_para)
     212      if (allocated(jj_end_para))   deallocate(jj_end_para)
     213      if (allocated(jj_nb_para))    deallocate(jj_nb_para)
    213214
    214215      if (type_ocean == 'couple') then
     
    549550       
    550551   
    551     /* 
    552   Subroutine verif_hallo(Field,ij,ll,up,down)
    553     implicit none
    554 #include "dimensions.h"
    555 #include "paramet.h"   
    556     include 'mpif.h'
    557    
    558       INTEGER :: ij,ll
    559       REAL, dimension(ij,ll) :: Field
    560       INTEGER :: up,down
    561      
    562       REAL,dimension(ij,ll): NewField
    563      
    564       NewField=0
    565      
    566       ijb=ij_begin
    567       ije=ij_end
    568       if (pole_nord)
    569       NewField(ij_be       
    570 */
     552!  Subroutine verif_hallo(Field,ij,ll,up,down)
     553!    implicit none
     554!#include "dimensions.h"
     555!#include "paramet.h"   
     556!    include 'mpif.h'
     557!   
     558!      INTEGER :: ij,ll
     559!      REAL, dimension(ij,ll) :: Field
     560!      INTEGER :: up,down
     561!     
     562!      REAL,dimension(ij,ll): NewField
     563!     
     564!      NewField=0
     565!     
     566!      ijb=ij_begin
     567!      ije=ij_end
     568!      if (pole_nord)
     569!      NewField(ij_be       
     570
    571571  end module parallel
  • 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
  • LMDZ5/trunk/makegcm

    r1403 r1492  
    2323set OPTIMI='-C debug -eC '
    2424set OPTIMI=' -ftrace '
    25 set OPT_LINUX='-O3'
    26 set OPT_LINUX="-i4 -r8 -O3"
     25set OPT_LINUX="-O3 -fdefault-real-8"
     26set OPT_LINUX="-O3 -fdefault-real-8"
    2727set io=ioipsl
    2828set cosp=false
    2929
    30 set FC_LINUX=g95
    3130set FC_LINUX=gfortran
    32 #set FC_LINUX=pgf90
    33 if ( $FC_LINUX == g95 ) then
    34    set OPT_LINUX="-O3"
    35    set OPT_LINUX="-O3"
     31set FC_LINUX=gfortran
     32#set FC_LINUX=gfortran
     33if ( $FC_LINUX == gfortran ) then
     34   set OPT_LINUX="-O3 -fdefault-real-8"
     35   set OPT_LINUX="-O3 -fdefault-real-8"
    3636else if ( $FC_LINUX == gfortran ) then
    37    set OPT_LINUX="-fdefault-real-8 -O3"
    38 #   set OPT_LINUX="-O3 -fno-second-underscore"
    39    set OPT_LINUX="-O3 "
     37   set OPT_LINUX="-O3 -fdefault-real-8"
     38#   set OPT_LINUX="-O3 -fdefault-real-8"
     39   set OPT_LINUX="-O3 -fdefault-real-8"
    4040else
    4141   # pgf90 options
    42    set OPT_LINUX="-i4 -r8 -O2 -Munroll -Mnoframe -Mautoinline -Mcache_align"
     42   set OPT_LINUX="-O3 -fdefault-real-8"
    4343endif
    4444
     
    5353#
    5454#
    55 setenv IOIPSLDIR /d4/fairhead/gfortran/ioipsl_v2_1_9
    56 setenv MODIPSLDIR /d4/fairhead/gfortran/ioipsl_v2_1_9
    57 setenv NCDFINC /d4/fairhead/gfortran_4.4/netcdf-4.1.1/include
    58 setenv NCDFLIB /d4/fairhead/gfortran_4.4/netcdf-4.1.1/lib
     55setenv IOIPSLDIR /d4/fairhead/LMDZ20100928.trunk/modipsl/lib
     56setenv MODIPSLDIR /d4/fairhead/LMDZ20100928.trunk/modipsl/lib
     57setenv NCDFINC /d4/fairhead/LMDZ20100928.trunk/netcdf-4.0.1/include
     58setenv NCDFLIB /d4/fairhead/LMDZ20100928.trunk/netcdf-4.0.1/lib
    5959
    6060
     
    108108  if ( ! $?NCDFLIB ) then
    109109    echo You must initialize the variable NCDFLIB in your environnement
    110     echo for instance: "setenv NCDFLIB /usr/myself/netcdf" in .cshrc
     110    echo for instance: "setenv NCDFLIB /d4/fairhead/LMDZ20100928.trunk/netcdf-4.0.1/lib
    111111    exit
    112112  endif
    113113  if ( ! $?NCDFINC ) then
    114114    echo You must initialize the variable NCDFINC in your environnement
    115     echo for instance: "setenv NCDFINC /usr/myself/netcdf" in .cshrc
     115    echo for instance: "setenv NCDFINC /d4/fairhead/LMDZ20100928.trunk/netcdf-4.0.1/include
    116116    exit
    117117  endif
     
    263263else if $LINUX then
    264264#################
    265    if ( $FC_LINUX == pgf90 || $FC_LINUX == g95 || $FC_LINUX == gfortran ) then
     265   if ( $FC_LINUX == pgf90 || $FC_LINUX == gfortran || $FC_LINUX == gfortran ) then
    266266     set optim=" $OPT_LINUX "
    267267     set optim90=" $OPT_LINUX "
     
    516516             set optim90="$optim90"" -g -C -Mbounds "
    517517             set optimtru90="$optimtru90"" -g -C -Mbounds "
    518            else if ( $FC_LINUX == 'g95' ) then
     518           else if ( $FC_LINUX == 'gfortran' ) then
    519519             set optim="$optim"" -g -fbounds-check "
    520520             set optim90="$optim90"" -g -fbounds-check "
     
    572572if ( "$veget" == 'true' ) then
    573573   set cppflags="$cppflags -DCPP_VEGET"
    574 #   set link_veget=" -lsechiba -lparameters -lstomate -lorglob -lparallel"
     574#   set link_veget=" -lsechiba -lparameters -lstomate  "
    575575   set link_veget=" -lsechiba -lparameters -lstomate"
    576576   if ( $XNEC || $X8BRODIE || $X6NEC) then
     
    833833       set opt_link=" -L$MODIPSLDIR $link_veget -L$NCDFLIB -lnetcdf "
    834834     endif
    835    else if ($FC_LINUX == 'g95' || $FC_LINUX == 'gfortran' ) then
     835   else if ($FC_LINUX == 'gfortran' || $FC_LINUX == 'gfortran' ) then
    836836     if ( $io == "ioipsl" ) then
    837837       set opt_link="-L$MODIPSLDIR $link_veget -lioipsl -L$NCDFLIB -lnetcdf -lioipsl -lnetcdf "
     
    10091009   set optimtru90=" $optimtru90 -module $libo "
    10101010   set optim90=" $optim90 -module $libo "
    1011  else if ( $FC_LINUX == 'g95' ) then
    1012    set optimtru90=" $optimtru90 -fmod=$libo  "
    1013    set optim90=" $optim90 -fmod=$libo  "
     1011 else if ( $FC_LINUX == 'gfortran' ) then
     1012   set optimtru90=" $optimtru90 -I$libo  "
     1013   set optim90=" $optim90 -I$libo  "
    10141014 else if ( $FC_LINUX == 'gfortran' ) then
    10151015   set optimtru90=" $optimtru90 -M $libo  "
Note: See TracChangeset for help on using the changeset viewer.