source: LMDZ4/branches/LMDZ4_AR5/libf/dyn3dpar/ce0l.F90 @ 1599

Last change on this file since 1599 was 1599, checked in by jghattas, 12 years ago

phys_output_mod - Bug in write : bad second argument in ioget_mon_len function.

ce0l - Changed finalize_parallel into mpi_finalize because the program ce0l did not finish correctly for case ocean_type=couple.

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 3.9 KB
Line 
1!
2! $Id: ce0l.F90 1599 2011-12-06 13:11:24Z jghattas $
3!
4!-------------------------------------------------------------------------------
5!
6PROGRAM ce0l
7!
8!-------------------------------------------------------------------------------
9! Purpose: Calls etat0, creates initial states and limit_netcdf
10!
11!     interbar=.T. for barycentric interpolation inter_barxy
12!     extrap  =.T. for data extrapolation, like for the SSTs when file does not
13!                  contain ocean points only.
14!     oldice  =.T. for old-style ice, obtained using grille_m (grid_atob).
15!     masque is created in etat0, passed to limit to ensure consistancy.
16!-------------------------------------------------------------------------------
17#ifdef CPP_EARTH
18! This prog. is designed to work for Earth
19  USE dimphy
20  USE comgeomphy
21  USE mod_phys_lmdz_para, mpi_root_xx=>mpi_root
22  USE mod_const_mpi
23  USE infotrac
24  USE parallel, ONLY: finalize_parallel
25
26#ifdef CPP_IOIPSL
27  USE ioipsl, ONLY: ioconf_calendar
28#endif
29
30#endif
31  IMPLICIT NONE
32#ifndef CPP_EARTH
33  WRITE(lunout,*)'limit_netcdf: Earth-specific routine, needs Earth physics'
34#else
35!-------------------------------------------------------------------------------
36! Local variables:
37  LOGICAL, PARAMETER :: interbar=.TRUE., extrap=.FALSE., oldice=.FALSE.
38#include "dimensions.h"
39#include "paramet.h"
40#include "indicesol.h"
41#include "iniprint.h"
42#include "control.h"
43#include "temps.h"
44#include "logic.h"
45#ifdef CPP_MPI
46      include 'mpif.h'
47#endif
48
49  INTEGER, PARAMETER            :: longcles=20
50  INTEGER                       :: ierr
51  REAL,    DIMENSION(longcles)  :: clesphy0
52  REAL,    DIMENSION(iip1,jjp1) :: masque
53  CHARACTER(LEN=15)             :: calnd
54 
55!-------------------------------------------------------------------------------
56  CALL conf_gcm( 99, .TRUE. , clesphy0 )
57
58#ifdef CPP_MPI
59  CALL init_mpi
60#endif
61
62  CALL Init_Phys_lmdz(iim,jjp1,llm,1,(/(jjm-1)*iim+2/))
63  WRITE(lunout,*)'---> klon=',klon
64  IF (mpi_size>1 .OR. omp_size>1) THEN
65       CALL abort_gcm('ce0l','In parallel mode,                         &
66 &                 ce0l must be called only                             &
67 &                 for 1 process and 1 task',1)
68  ENDIF
69
70  CALL InitComgeomphy
71
72#ifdef CPP_IOIPSL
73  SELECT CASE(calend)
74    CASE('earth_360d');CALL ioconf_calendar('360d');      calnd='a 360 jours/an'
75    CASE('earth_365d');CALL ioconf_calendar('noleap');    calnd='a 365 jours/an'
76    CASE('earth_366d');CALL ioconf_calendar('366d');      calnd='bissextile'
77    CASE('gregorian'); CALL ioconf_calendar('gregorian'); calnd='gregorien'
78    CASE('standard');  CALL ioconf_calendar('gregorian'); calnd='gregorien'
79    CASE('julian');    CALL ioconf_calendar('julian');    calnd='julien'
80    CASE('proleptic_gregorian'); CALL ioconf_calendar('gregorian')
81  !--- DC Bof...  => IOIPSL a mettre a jour: proleptic_gregorian /= gregorian
82    CASE DEFAULT
83      CALL abort_gcm('ce0l','Mauvais choix de calendrier',1)
84  END SELECT
85  WRITE(lunout,*)'CALENDRIER CHOISI: Terrestre '//TRIM(calnd)
86#endif
87
88  IF (config_inca /= 'none') THEN
89#ifdef INCA
90    CALL init_const_lmdz(nbtr,anneeref,dayref,iphysiq,day_step,nday)
91    CALL init_inca_para(iim,jjm+1,klon,1,klon_mpi_para_nb,0)
92    WRITE(lunout,*)'nbtr =' , nbtr
93#endif
94  END IF
95
96  WRITE(lunout,'(//)')
97  WRITE(lunout,*) '  *********************  '
98  WRITE(lunout,*) '  ***  etat0_netcdf ***  '
99  WRITE(lunout,*) '  *********************  '
100  WRITE(lunout,'(//)')
101  WRITE(lunout,*) ' interbar = ',interbar
102  CALL etat0_netcdf(interbar,masque,ok_etat0)
103
104  IF(ok_limit) THEN
105  WRITE(lunout,'(//)')
106  WRITE(lunout,*) '  *********************  '
107  WRITE(lunout,*) '  ***  Limit_netcdf ***  '
108  WRITE(lunout,*) '  *********************  '
109  WRITE(lunout,'(//)')
110  CALL limit_netcdf(interbar,extrap,oldice,masque)
111  END IF
112
113#ifdef CPP_MPI
114!$OMP MASTER
115  CALL MPI_FINALIZE(ierr)
116  IF (ierr /= 0) CALL abort_gcm('ce0l','Error in MPI_FINALIZE',1)
117!$OMP END MASTER
118#endif
119
120
121#endif
122! of #ifndef CPP_EARTH #else
123
124END PROGRAM ce0l
125!
126!-------------------------------------------------------------------------------
Note: See TracBrowser for help on using the repository browser.