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:
4 deleted
10 edited
5 copied

Legend:

Unmodified
Added
Removed
  • LMDZ5/trunk

  • 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
Note: See TracChangeset for help on using the changeset viewer.