source: LMDZ5/trunk/libf/dyn3dmem/ce0l.F90 @ 2247

Last change on this file since 2247 was 2221, checked in by Ehouarn Millour, 9 years ago

Some cleanup: remove (unused) clesph0 from dynamics.
EM

  • Property copyright set to
    Name of program: LMDZ
    Creation date: 1984
    Version: LMDZ5
    License: CeCILL version 2
    Holder: Laboratoire de m\'et\'eorologie dynamique, CNRS, UMR 8539
    See the license file in the root directory
File size: 4.2 KB
Line 
1!
2! $Id$
3!
4!-------------------------------------------------------------------------------
5!
6PROGRAM ce0l
7!-------------------------------------------------------------------------------
8! Purpose: Calls etat0, creates initial states and limit_netcdf
9!
10!     interbar=.T. for barycentric interpolation inter_barxy
11!     extrap  =.T. for data extrapolation, like for the SSTs when file does not
12!                  contain ocean points only.
13!     oldice  =.T. for old-style ice, obtained using grille_m (grid_atob).
14!     masque is created in etat0, passed to limit to ensure consistancy.
15!-------------------------------------------------------------------------------
16  USE control_mod
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_lmdz, ONLY: finalize_parallel 
25  USE indice_sol_mod
26
27#ifdef CPP_IOIPSL
28  USE ioipsl, ONLY: ioconf_calendar
29#endif
30
31#endif
32  IMPLICIT NONE
33#ifndef CPP_EARTH
34#include "iniprint.h"
35  WRITE(lunout,*)'limit_netcdf: Earth-specific routine, needs Earth physics'
36#else
37!-------------------------------------------------------------------------------
38! Local variables:
39  LOGICAL, PARAMETER :: interbar=.TRUE., extrap=.FALSE., oldice=.FALSE.
40#include "dimensions.h"
41#include "paramet.h"
42!#include "indicesol.h"
43#include "iniprint.h"
44#include "temps.h"
45#include "logic.h"
46#ifdef CPP_MPI
47      include 'mpif.h'
48#endif
49
50  INTEGER                       :: ierr
51  REAL,    DIMENSION(iip1,jjp1) :: masque
52  CHARACTER(LEN=15)             :: calnd
53  REAL,    DIMENSION(iip1,jjp1) :: phis ! geopotentiel au sol
54!-------------------------------------------------------------------------------
55  CALL conf_gcm( 99, .TRUE. )
56
57#ifdef CPP_MPI
58  CALL init_mpi
59#endif
60
61  CALL Init_Phys_lmdz(iim,jjp1,llm,1,(/(jjm-1)*iim+2/))
62  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
69  CALL InitComgeomphy
70
71#ifdef CPP_IOIPSL
72  SELECT CASE(calend)
73    CASE('earth_360d');CALL ioconf_calendar('360d');      calnd='a 360 jours/an'
74    CASE('earth_365d');CALL ioconf_calendar('noleap');    calnd='a 365 jours/an'
75    CASE('earth_366d');CALL ioconf_calendar('366d');      calnd='bissextile'
76    CASE('gregorian'); CALL ioconf_calendar('gregorian'); calnd='gregorien'
77    CASE('standard');  CALL ioconf_calendar('gregorian'); calnd='gregorien'
78    CASE('julian');    CALL ioconf_calendar('julian');    calnd='julien'
79    CASE('proleptic_gregorian'); CALL ioconf_calendar('gregorian')
80  !--- DC Bof...  => IOIPSL a mettre a jour: proleptic_gregorian /= gregorian
81    CASE DEFAULT
82      CALL abort_gcm('ce0l','Mauvais choix de calendrier',1)
83  END SELECT
84  WRITE(lunout,*)'CALENDRIER CHOISI: Terrestre '//TRIM(calnd)
85#endif
86
87  IF (type_trac == 'inca') THEN
88#ifdef INCA
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     
95#endif
96  END IF
97
98  WRITE(lunout,'(//)')
99  WRITE(lunout,*) '  *********************  '
100  WRITE(lunout,*) '  ***  etat0_netcdf ***  '
101  WRITE(lunout,*) '  *********************  '
102  WRITE(lunout,'(//)')
103  WRITE(lunout,*) ' interbar = ',interbar
104  CALL etat0_netcdf(interbar,masque,phis,ok_etat0)
105
106  IF(ok_limit) THEN
107  WRITE(lunout,'(//)')
108  WRITE(lunout,*) '  *********************  '
109  WRITE(lunout,*) '  ***  Limit_netcdf ***  '
110  WRITE(lunout,*) '  *********************  '
111  WRITE(lunout,'(//)')
112  CALL limit_netcdf(interbar,extrap,oldice,masque)
113  END IF
114
115  WRITE(lunout,'(//)')
116  WRITE(lunout,*) '  ***************************  '
117  WRITE(lunout,*) '  ***  grilles_gcm_netcdf ***  '
118  WRITE(lunout,*) '  ***************************  '
119  WRITE(lunout,'(//)')
120  CALL grilles_gcm_netcdf_sub(masque,phis)
121 
122#ifdef CPP_MPI
123!$OMP MASTER
124  CALL MPI_FINALIZE(ierr)
125  IF (ierr /= 0) CALL abort_gcm('ce0l','Error in MPI_FINALIZE',1)
126!$OMP END MASTER
127#endif
128
129#endif
130! of #ifndef CPP_EARTH #else
131
132END PROGRAM ce0l
133!
134!-------------------------------------------------------------------------------
Note: See TracBrowser for help on using the repository browser.