Ignore:
Timestamp:
Jan 5, 2012, 8:28:41 AM (13 years ago)
Author:
emillour
Message:

Common dynamics: updates to keep up with LMDZ5 Earth (rev 1605)
See file "DOC/chantiers/commit_importants.log" for details.
EM

File:
1 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.COMMON/libf/dyn3dpar/ce0l.F90

    r270 r492  
    11!
    2 ! $Id: ce0l.F90 1511 2011-04-28 15:21:47Z jghattas $
     2! $Id: ce0l.F90 1600 2011-12-06 13:16:30Z jghattas $
    33!
    44!-------------------------------------------------------------------------------
     
    1919  USE dimphy
    2020  USE comgeomphy
     21  USE mod_phys_lmdz_para, mpi_root_xx=>mpi_root
     22  USE mod_const_mpi
    2123  USE infotrac
     24  USE parallel, ONLY: finalize_parallel
    2225
    2326#ifdef CPP_IOIPSL
     
    2831  IMPLICIT NONE
    2932#ifndef CPP_EARTH
    30   WRITE(lunout,*)'limit_netcdf: Earth-specific routine, needs Earth physics'
     33  WRITE(*,*)'limit_netcdf: Earth-specific routine, needs Earth physics'
    3134#else
    3235!-------------------------------------------------------------------------------
     
    3942#include "temps.h"
    4043#include "logic.h"
     44#ifdef CPP_MPI
     45      include 'mpif.h'
     46#endif
     47
    4148  INTEGER, PARAMETER            :: longcles=20
     49  INTEGER                       :: ierr
    4250  REAL,    DIMENSION(longcles)  :: clesphy0
    4351  REAL,    DIMENSION(iip1,jjp1) :: masque
     
    4755  CALL conf_gcm( 99, .TRUE. , clesphy0 )
    4856
     57#ifdef CPP_MPI
     58  CALL init_mpi
     59#endif
     60
    4961  CALL Init_Phys_lmdz(iim,jjp1,llm,1,(/(jjm-1)*iim+2/))
    5062  WRITE(lunout,*)'---> klon=',klon
     63  IF (mpi_size>1 .OR. omp_size>1) THEN
     64       CALL abort_gcm('ce0l','In parallel mode,                         &
     65 &                 ce0l must be called only                             &
     66 &                 for 1 process and 1 task',1)
     67  ENDIF
     68
    5169  CALL InitComgeomphy
    5270
     
    6785#endif
    6886
    69   IF (config_inca /= 'none') THEN
     87  IF (type_trac == 'inca') THEN
    7088#ifdef INCA
    71     CALL init_const_lmdz(nbtr,anneeref,dayref,iphysiq,day_step,nday)
    72     CALL init_inca_para(iim,jjm+1,klon,1,klon_mpi_para_nb,0)
    73     WRITE(lunout,*)'nbtr =' , nbtr
     89      CALL init_const_lmdz( &
     90         nbtr,anneeref,dayref,&
     91         iphysiq,day_step,nday,&
     92         nbsrf, is_oce,is_sic,&
     93         is_ter,is_lic)
     94     
    7495#endif
    7596  END IF
     
    100121     CALL grilles_gcm_netcdf_sub(masque,phis)
    101122  END IF
     123 
     124#ifdef CPP_MPI
     125!$OMP MASTER
     126  CALL MPI_FINALIZE(ierr)
     127  IF (ierr /= 0) CALL abort_gcm('ce0l','Error in MPI_FINALIZE',1)
     128!$OMP END MASTER
     129#endif
     130
    102131#endif
    103132! of #ifndef CPP_EARTH #else
Note: See TracChangeset for help on using the changeset viewer.