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

Last change on this file since 2247 was 2247, checked in by lguez, 9 years ago

We want to keep the same "*.def" files with programs ce0l and gcm. But
there is only a sequential version of program ce0l, which has not the
FFT filter. So we have to ignore the setting of use_filtre_fft in
program ce0l. Moved the test on use_filtre_fft from procedure conf_gcm
to main units ce0l and gcm.

  • 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
  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 4.0 KB
Line 
1!
2! $Id: ce0l.F90 2247 2015-03-25 17:24:15Z 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 infotrac
22  USE indice_sol_mod
23
24#ifdef CPP_IOIPSL
25  USE ioipsl, ONLY: ioconf_calendar, getin
26#else
27  ! if not using IOIPSL, we still need to use (a local version of) getin
28  use ioipsl_getincom, only: getin
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  REAL,    DIMENSION(iip1,jjp1) :: masque
47  CHARACTER(LEN=15)             :: calnd
48  REAL,    DIMENSION(iip1,jjp1) :: phis ! geopotentiel au sol
49  logical use_filtre_fft
50!-------------------------------------------------------------------------------
51  CALL conf_gcm( 99, .TRUE. )
52
53  use_filtre_fft=.FALSE.
54  CALL getin('use_filtre_fft',use_filtre_fft)
55  IF (use_filtre_fft) THEN
56     write(lunout, fmt = *) 'FFT filter is not available in the ' &
57          // 'sequential version of the dynamics.'
58     write(lunout, fmt = *) &
59          "Your setting of variable use_filtre_fft is not used."
60  ENDIF
61
62  CALL Init_Phys_lmdz(iim,jjp1,llm,1,(/(jjm-1)*iim+2/))
63  WRITE(lunout,*)'---> klon=',klon
64  CALL InitComgeomphy
65
66#ifdef CPP_IOIPSL
67  SELECT CASE(calend)
68    CASE('earth_360d');CALL ioconf_calendar('360d');      calnd='a 360 jours/an'
69    CASE('earth_365d');CALL ioconf_calendar('noleap');    calnd='a 365 jours/an'
70    CASE('earth_366d');CALL ioconf_calendar('366d');      calnd='bissextile'
71    CASE('gregorian'); CALL ioconf_calendar('gregorian'); calnd='gregorien'
72    CASE('standard');  CALL ioconf_calendar('gregorian'); calnd='gregorien'
73    CASE('julian');    CALL ioconf_calendar('julian');    calnd='julien'
74    CASE('proleptic_gregorian'); CALL ioconf_calendar('gregorian')
75  !--- DC Bof...  => IOIPSL a mettre a jour: proleptic_gregorian /= gregorian
76    CASE DEFAULT
77      CALL abort_gcm('ce0l','Mauvais choix de calendrier',1)
78  END SELECT
79  WRITE(lunout,*)'CALENDRIER CHOISI: Terrestre '//TRIM(calnd)
80#endif
81
82  IF (type_trac == 'inca') THEN
83#ifdef INCA
84    CALL init_const_lmdz(nbtr,anneeref,dayref,iphysiq,day_step,nday)
85    CALL init_inca_para(iim,jjm+1,klon,1,klon_mpi_para_nb,0)
86    WRITE(lunout,*)'nbtr =' , nbtr
87#endif
88  END IF
89
90  WRITE(lunout,'(//)')
91  WRITE(lunout,*) '  *********************  '
92  WRITE(lunout,*) '  ***  etat0_netcdf ***  '
93  WRITE(lunout,*) '  *********************  '
94  WRITE(lunout,'(//)')
95  WRITE(lunout,*) ' interbar = ',interbar
96  CALL etat0_netcdf(interbar,masque,phis,ok_etat0)
97
98  IF(ok_limit) THEN
99  WRITE(lunout,'(//)')
100  WRITE(lunout,*) '  *********************  '
101  WRITE(lunout,*) '  ***  Limit_netcdf ***  '
102  WRITE(lunout,*) '  *********************  '
103  WRITE(lunout,'(//)')
104  CALL limit_netcdf(interbar,extrap,oldice,masque)
105  END IF
106
107 
108  WRITE(lunout,'(//)')
109  WRITE(lunout,*) '  ***************************  '
110  WRITE(lunout,*) '  ***  grilles_gcm_netcdf ***  '
111  WRITE(lunout,*) '  ***************************  '
112  WRITE(lunout,'(//)')
113  CALL grilles_gcm_netcdf_sub(masque,phis)
114
115#endif
116! of #ifndef CPP_EARTH #else
117
118END PROGRAM ce0l
119!
120!-------------------------------------------------------------------------------
Note: See TracBrowser for help on using the repository browser.