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

Last change on this file since 1660 was 1658, checked in by Laurent Fairhead, 12 years ago

Phasage de la dynamique parallele localisee (petite memoire) avec le tronc LMDZ4 (HEAD)
Validation effectuee par comparaison des fichiers de sorties debug (u, v, t, q, masse, etc ...) d'une simulation sans physique
faite avec la version du modele donnee par Y. Meurdesoif et la version phasee avec la r1428 (fin du tronc LMDZ4)


Phasing of the localised (low memory) parallel dynamics package with the LMDZ4 trunk version of LMDZ
Validation consisted in comparing output debug files (u, v, t, q, masse, etc... ) of a no physics simulation
run with the version of the code given by Y. Meurdesoif and this version phased with r1428 (HEAD of the LMDZ4 trunk)

File size: 3.7 KB
Line 
1!
2! $Id: ce0l.F90 1425 2010-09-02 13:45:23Z lguez $
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
22  USE mod_const_mpi
23  USE infotrac
24
25#ifdef CPP_IOIPSL
26  USE ioipsl, ONLY: ioconf_calendar
27#endif
28
29#endif
30  IMPLICIT NONE
31#ifndef CPP_EARTH
32  WRITE(lunout,*)'limit_netcdf: Earth-specific routine, needs Earth physics'
33#else
34!-------------------------------------------------------------------------------
35! Local variables:
36  LOGICAL, PARAMETER :: interbar=.TRUE., extrap=.FALSE., oldice=.FALSE.
37#include "dimensions.h"
38#include "paramet.h"
39#include "indicesol.h"
40#include "iniprint.h"
41#include "temps.h"
42#include "logic.h"
43  INTEGER, PARAMETER            :: longcles=20
44  REAL,    DIMENSION(longcles)  :: clesphy0
45  REAL,    DIMENSION(iip1,jjp1) :: masque
46  CHARACTER(LEN=15)             :: calnd
47!-------------------------------------------------------------------------------
48  CALL conf_gcm( 99, .TRUE. , clesphy0 )
49
50  CALL init_mpi
51
52  CALL Init_Phys_lmdz(iim,jjp1,llm,1,(/(jjm-1)*iim+2/))
53  WRITE(lunout,*)'---> klon=',klon
54  IF (mpi_size>1 .OR. omp_size>1) THEN
55       CALL abort_gcm('ce0l','In parallel mode,                         &
56 &                 ce0l must be called only                             &
57 &                 for 1 process and 1 task')
58  ENDIF
59
60  CALL InitComgeomphy
61
62#ifdef CPP_IOIPSL
63  SELECT CASE(calend)
64    CASE('earth_360d');CALL ioconf_calendar('360d');      calnd='a 360 jours/an'
65    CASE('earth_365d');CALL ioconf_calendar('noleap');    calnd='a 365 jours/an'
66    CASE('earth_366d');CALL ioconf_calendar('366d');      calnd='bissextile'
67    CASE('gregorian'); CALL ioconf_calendar('gregorian'); calnd='gregorien'
68    CASE('standard');  CALL ioconf_calendar('gregorian'); calnd='gregorien'
69    CASE('julian');    CALL ioconf_calendar('julian');    calnd='julien'
70    CASE('proleptic_gregorian'); CALL ioconf_calendar('gregorian')
71  !--- DC Bof...  => IOIPSL a mettre a jour: proleptic_gregorian /= gregorian
72    CASE DEFAULT
73      CALL abort_gcm('ce0l','Mauvais choix de calendrier',1)
74  END SELECT
75  WRITE(lunout,*)'CALENDRIER CHOISI: Terrestre '//TRIM(calnd)
76#endif
77
78  IF (config_inca /= 'none') THEN
79#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
83#endif
84  END IF
85
86  WRITE(lunout,'(//)')
87  WRITE(lunout,*) '  *********************  '
88  WRITE(lunout,*) '  ***  etat0_netcdf ***  '
89  WRITE(lunout,*) '  *********************  '
90  WRITE(lunout,'(//)')
91  WRITE(lunout,*) ' interbar = ',interbar
92  CALL etat0_netcdf(interbar,masque,ok_etat0)
93
94  IF(ok_limit) THEN
95  WRITE(lunout,'(//)')
96  WRITE(lunout,*) '  *********************  '
97  WRITE(lunout,*) '  ***  Limit_netcdf ***  '
98  WRITE(lunout,*) '  *********************  '
99  WRITE(lunout,'(//)')
100  CALL limit_netcdf(interbar,extrap,oldice,masque)
101  END IF
102
103#endif
104! of #ifndef CPP_EARTH #else
105
106END PROGRAM ce0l
107!
108!-------------------------------------------------------------------------------
Note: See TracBrowser for help on using the repository browser.