Ignore:
Timestamp:
Jan 11, 2013, 10:19:19 AM (11 years ago)
Author:
Laurent Fairhead
Message:

Version testing basée sur la r1706


Testing release based on r1706

Location:
LMDZ5/branches/testing
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • LMDZ5/branches/testing

  • LMDZ5/branches/testing/libf/dyn3dmem/ce0l.F90

    r1669 r1707  
    11!
    2 ! $Id: ce0l.F90 1425 2010-09-02 13:45:23Z lguez $
     2! $Id$
    33!
    44!-------------------------------------------------------------------------------
     
    1919  USE dimphy
    2020  USE comgeomphy
    21   USE mod_phys_lmdz_para
     21  USE mod_phys_lmdz_para, mpi_root_xx=>mpi_root
    2222  USE mod_const_mpi
    2323  USE infotrac
     24  USE parallel, ONLY: finalize_parallel
    2425
    2526#ifdef CPP_IOIPSL
     
    3031  IMPLICIT NONE
    3132#ifndef CPP_EARTH
     33#include "iniprint.h"
    3234  WRITE(lunout,*)'limit_netcdf: Earth-specific routine, needs Earth physics'
    3335#else
     
    4143#include "temps.h"
    4244#include "logic.h"
     45#ifdef CPP_MPI
     46      include 'mpif.h'
     47#endif
     48
    4349  INTEGER, PARAMETER            :: longcles=20
     50  INTEGER                       :: ierr
    4451  REAL,    DIMENSION(longcles)  :: clesphy0
    4552  REAL,    DIMENSION(iip1,jjp1) :: masque
    4653  CHARACTER(LEN=15)             :: calnd
     54  REAL,    DIMENSION(iip1,jjp1) :: phis ! geopotentiel au sol
    4755!-------------------------------------------------------------------------------
    4856  CALL conf_gcm( 99, .TRUE. , clesphy0 )
    4957
     58#ifdef CPP_MPI
    5059  CALL init_mpi
     60#endif
    5161
    5262  CALL Init_Phys_lmdz(iim,jjp1,llm,1,(/(jjm-1)*iim+2/))
     
    5565       CALL abort_gcm('ce0l','In parallel mode,                         &
    5666 &                 ce0l must be called only                             &
    57  &                 for 1 process and 1 task')
     67 &                 for 1 process and 1 task',1)
    5868  ENDIF
    5969
     
    7686#endif
    7787
    78   IF (config_inca /= 'none') THEN
     88  IF (type_trac == 'inca') THEN
    7989#ifdef INCA
    80     CALL init_const_lmdz(nbtr,anneeref,dayref,iphysiq,day_step,nday)
    81     CALL init_inca_para(iim,jjm+1,klon,1,klon_mpi_para_nb,0)
    82     WRITE(lunout,*)'nbtr =' , nbtr
     90      CALL init_const_lmdz( &
     91         nbtr,anneeref,dayref,&
     92         iphysiq,day_step,nday,&
     93         nbsrf, is_oce,is_sic,&
     94         is_ter,is_lic)
     95     
    8396#endif
    8497  END IF
     
    90103  WRITE(lunout,'(//)')
    91104  WRITE(lunout,*) ' interbar = ',interbar
    92   CALL etat0_netcdf(interbar,masque,ok_etat0)
     105  CALL etat0_netcdf(interbar,masque,phis,ok_etat0)
    93106
    94107  IF(ok_limit) THEN
     
    101114  END IF
    102115
     116  IF (grilles_gcm_netcdf) THEN
     117     WRITE(lunout,'(//)')
     118     WRITE(lunout,*) '  ***************************  '
     119     WRITE(lunout,*) '  ***  grilles_gcm_netcdf ***  '
     120     WRITE(lunout,*) '  ***************************  '
     121     WRITE(lunout,'(//)')
     122     CALL grilles_gcm_netcdf_sub(masque,phis)
     123  END IF
     124 
     125#ifdef CPP_MPI
     126!$OMP MASTER
     127  CALL MPI_FINALIZE(ierr)
     128  IF (ierr /= 0) CALL abort_gcm('ce0l','Error in MPI_FINALIZE',1)
     129!$OMP END MASTER
     130#endif
     131
    103132#endif
    104133! of #ifndef CPP_EARTH #else
Note: See TracChangeset for help on using the changeset viewer.