source: LMDZ5/trunk/libf/dynlonlat_phylonlat/phylmd/ce0l.F90 @ 2405

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

Correction for ce0l to compile and work in serial mode.
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
  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 8.3 KB
RevLine 
[2293]1PROGRAM ce0l
[2336]2!
3!-------------------------------------------------------------------------------
4! Purpose: Initial states and boundary conditions files creation:
5!     * start.nc    for dynamics    (using etat0dyn     routine)
6!     * startphy.nc for physics     (using etat0phys    routine)
7!     * limit.nc    for forced runs (using limit_netcdf routine)
8!-------------------------------------------------------------------------------
9! Notes:
10!     * extrap=.T. (default) for data extrapolation, like for the SSTs when file
11!                   does contain ocean points only.
12!     * "masque" can be:
13!       - read from file "o2a.nc"          (for coupled runs).
14!       - created in etat0phys or etat0dyn (for forced  runs).
15!     It is then passed to limit_netcdf to ensure consistancy.
16!-------------------------------------------------------------------------------
[2293]17  USE ioipsl, ONLY: ioconf_calendar, getin, flininfo, flinopen, flinget, flinclo
[2336]18  USE control_mod,    ONLY: day_step, dayref, nsplit_phys
19  USE etat0dyn,       ONLY: etat0dyn_netcdf
20  USE etat0phys,      ONLY: etat0phys_netcdf
21  USE limit,          ONLY: limit_netcdf
22  USE netcdf,         ONLY: NF90_OPEN, NF90_NOWRITE, NF90_CLOSE, NF90_NOERR
23  USE infotrac,       ONLY: type_trac, infotrac_init
24  USE dimphy,         ONLY: klon
[2293]25  USE test_disvert_m, ONLY: test_disvert
[2336]26  USE filtreg_mod,    ONLY: inifilr
[2349]27  USE iniphysiq_mod,  ONLY: iniphysiq
[2351]28  USE mod_const_mpi,  ONLY: comm_lmdz
[2336]29#ifdef inca
30  USE indice_sol_mod, ONLY: nbsrf, is_oce, is_sic, is_ter, is_lic
31#endif
32#ifdef CPP_PARA
33  USE mod_const_mpi,  ONLY: init_const_mpi
34  USE parallel_lmdz,  ONLY: init_parallel, mpi_rank, omp_rank, mpi_size
35  USE bands,          ONLY: read_distrib, distrib_phys
36  USE mod_hallo,      ONLY: init_mod_hallo
37  USE mod_interface_dyn_phys, ONLY: init_interface_dyn_phys
38#endif
[524]39
[1319]40  IMPLICIT NONE
[2293]41
[2336]42!-------------------------------------------------------------------------------
43! Local variables:
[2293]44  include "dimensions.h"
45  include "paramet.h"
[2336]46  include "comgeom2.h"
[2293]47  include "comconst.h"
48  include "comvert.h"
49  include "iniprint.h"
50  include "temps.h"
51  include "logic.h"
[2336]52  REAL               :: masque(iip1,jjp1)             !--- CONTINENTAL MASK
53  REAL               :: phis  (iip1,jjp1)             !--- GROUND GEOPOTENTIAL
[2293]54  CHARACTER(LEN=256) :: modname, fmt, calnd           !--- CALENDAR TYPE
55  LOGICAL            :: use_filtre_fft
[2336]56  LOGICAL, PARAMETER :: extrap=.FALSE.
[2293]57
[2336]58!--- Local variables for ocean mask reading:
[2293]59  INTEGER            :: nid_o2a, iml_omask, jml_omask, j
60  INTEGER            :: fid, iret, llm_tmp, ttm_tmp, itaul(1)
[2336]61  REAL, ALLOCATABLE  :: lon_omask(:,:), dlon_omask(:), ocemask(:,:)
62  REAL, ALLOCATABLE  :: lat_omask(:,:), dlat_omask(:), ocetmp (:,:)
[2293]63  REAL               :: date, lev(1)
[2353]64#ifndef CPP_PARA
65! for iniphysiq in serial mode
66  INTEGER,PARAMETER :: mpi_rank=0
67  INTEGER :: distrib_phys(mpi_rank:mpi_rank)=(jjm-1)*iim+2
68#endif
[2336]69!-------------------------------------------------------------------------------
[2293]70  modname="ce0l"
71
[2336]72!--- Constants
[2293]73  pi     = 4. * ATAN(1.)
74  rad    = 6371229.
75  daysec = 86400.
76  omeg   = 2.*pi/daysec
77  g      = 9.8
78  kappa  = 0.2857143
79  cpp    = 1004.70885
80  jmp1   = jjm + 1
81  preff   = 101325.
82  pa      = 50000.
83
[2221]84  CALL conf_gcm( 99, .TRUE. )
[2331]85  dtvr = daysec/REAL(day_step)
[2336]86  WRITE(lunout,*)'dtvr',dtvr
[2293]87  CALL iniconst()
88  CALL inigeom()
[822]89
[2336]90!--- Calendar choice
[1279]91#ifdef CPP_IOIPSL
[2293]92  calnd='gregorian'
[1319]93  SELECT CASE(calend)
[2336]94    CASE('earth_360d');CALL ioconf_calendar('360d');   calnd='with 360 days/year'
95    CASE('earth_365d');CALL ioconf_calendar('noleap'); calnd='with no leap year'
96    CASE('earth_366d');CALL ioconf_calendar('366d');   calnd='with leap years only'
97    CASE('gregorian'); CALL ioconf_calendar('gregorian')
98    CASE('standard');  CALL ioconf_calendar('gregorian')
99    CASE('julian');    CALL ioconf_calendar('julian'); calnd='julian'
100    CASE('proleptic_gregorian'); CALL ioconf_calendar('gregorian')
101  !--- DC Bof...  => IOIPSL a mettre a jour: proleptic_gregorian /= gregorian
102    CASE DEFAULT
103      CALL abort_gcm('ce0l','Bad choice for calendar',1)
[1319]104  END SELECT
[2336]105  WRITE(lunout,*)'CHOSEN CALENDAR: Earth '//TRIM(calnd)
[1279]106#endif
107
[2336]108#ifdef CPP_PARA
109!--- Physical grid + parallel initializations
110  CALL init_const_mpi()
111  CALL init_parallel()
112  CALL read_distrib()
113  CALL init_mod_hallo()
114#endif
115  WRITE(lunout,*)'---> klon=',klon
116
117!--- Tracers initializations
118  IF (type_trac == 'inca') THEN
119#ifdef INCA
120    CALL init_const_lmdz(nbtr,anneeref,dayref,iphysiq,day_step,nday,&
121                         nbsrf,is_oce,is_sic,is_ter,is_lic,calend)
122    CALL init_inca_para(iim,jjp1,llm,klon_glo,mpi_size,distrib_phys,&
123                        COMM_LMDZ)
124    WRITE(lunout,*)'nbtr =' , nbtr
125#endif
126  END IF
127  CALL infotrac_init()
128
129  CALL inifilr()
[2351]130  CALL iniphysiq(iim,jjm,llm, &
131                 distrib_phys(mpi_rank),comm_lmdz, &
132                 daysec,day_ini,dtphys/nsplit_phys, &
[2349]133                 rlatu,rlatv,rlonu,rlonv,aire,cu,cv,rad,g,r,cpp,iflag_phys)
[2336]134  IF(pressure_exner) CALL test_disvert
135
136#ifdef CPP_PARA
137  IF (mpi_rank==0.AND.omp_rank==0) THEN
138#endif
[2293]139  use_filtre_fft=.FALSE.
[2336]140  CALL getin('use_filtre_fft',use_filtre_fft)
[2293]141  IF(use_filtre_fft) THEN
[2336]142     WRITE(lunout,*)"FFT filter not available for sequential dynamics."
143     WRITE(lunout,*)"Your setting of variable use_filtre_fft is not used."
[2293]144  ENDIF
145
[2336]146!--- LAND MASK. TWO CASES:
147!   1) read from ocean model    file "o2a.nc"    (coupled runs)
148!   2) computed from topography file "Relief.nc" (masque(:,:)=-99999.)
149! Coupled simulations (case 1) use the ocean model mask to compute the
150! weights to ensure ocean fractions are the same for atmosphere and ocean.
151!*******************************************************************************
[2293]152  IF(NF90_OPEN("o2a.nc", NF90_NOWRITE, nid_o2a)/=NF90_NOERR) THEN
[2336]153    WRITE(lunout,*)'BEWARE !! No ocean mask "o2a.nc" file found'
154    WRITE(lunout,*)'Forced run.'
155    masque(:,:)=-99999.
[2293]156  ELSE
[2336]157    iret=NF90_CLOSE(nid_o2a)
158    WRITE(lunout,*)'BEWARE !! Ocean mask "o2a.nc" file found'
159    WRITE(lunout,*)'Coupled run.'
160    CALL flininfo("o2a.nc", iml_omask, jml_omask, llm_tmp, ttm_tmp, nid_o2a)
161    IF(iml_omask/=iim .OR.jml_omask/=jjp1) THEN
162      WRITE(lunout,*)'Mismatching dimensions for ocean mask'
163      WRITE(lunout,*)'iim  = ',iim ,' iml_omask = ',iml_omask
164      WRITE(lunout,*)'jjp1 = ',jjp1,' jml_omask = ',jml_omask
165      CALL abort_gcm(modname,'',1)
166    END IF
167    ALLOCATE(ocemask(iim,jjp1),lon_omask(iim,jjp1),dlon_omask(iim ))
168    ALLOCATE(ocetmp (iim,jjp1),lat_omask(iim,jjp1),dlat_omask(jjp1))
[2338]169    CALL flinopen("o2a.nc", .FALSE.,iml_omask,jml_omask,llm_tmp,               &
170                  lon_omask,lat_omask,lev,ttm_tmp,itaul,date,dt,fid)
[2336]171    CALL flinget(fid, "OceMask",    iim,jjp1,llm_tmp,ttm_tmp,1,1,ocetmp)
172    CALL flinclo(fid)
173    dlon_omask(1:iim ) = lon_omask(1:iim,1)
174    dlat_omask(1:jjp1) = lat_omask(1,1:jjp1)
175    ocemask = ocetmp
176    IF(dlat_omask(1)<dlat_omask(jml_omask)) THEN
177      DO j=1,jjp1; ocemask(:,j) = ocetmp(:,jjp1-j+1); END DO
178    END IF
179    DEALLOCATE(ocetmp,lon_omask,lat_omask,dlon_omask,dlat_omask)
180    IF(prt_level>=1) THEN
181      WRITE(fmt,"(i4,'i1)')")iim ; fmt='('//ADJUSTL(fmt)
182      WRITE(lunout,*)'OCEAN MASK :'
183      WRITE(lunout,fmt) NINT(ocemask)
184    END IF
185    masque(1:iim,:)=1.-ocemask(:,:)
186    masque(iip1 ,:)=masque(1,:)
187    DEALLOCATE(ocemask)
[2293]188  END IF
[2336]189  phis(:,:)=-99999.
[2293]190
191  IF(ok_etat0) THEN
[2336]192    WRITE(lunout,'(//)')
193    WRITE(lunout,*) '  ************************  '
194    WRITE(lunout,*) '  ***  etat0phy_netcdf ***  '
195    WRITE(lunout,*) '  ************************  '
196    CALL etat0phys_netcdf(masque,phis)
197    WRITE(lunout,'(//)')
198    WRITE(lunout,*) '  ************************  '
199    WRITE(lunout,*) '  ***  etat0dyn_netcdf ***  '
200    WRITE(lunout,*) '  ************************  '
201    CALL etat0dyn_netcdf(masque,phis)
[2293]202  END IF
[524]203
[2336]204  IF(ok_limit) THEN
205    WRITE(lunout,'(//)')
206    WRITE(lunout,*) '  *********************  '
207    WRITE(lunout,*) '  ***  Limit_netcdf ***  '
208    WRITE(lunout,*) '  *********************  '
209    WRITE(lunout,'(//)')
210    CALL limit_netcdf(masque,phis,extrap)
[2293]211  END IF
[524]212
[2336]213  WRITE(lunout,'(//)')
214  WRITE(lunout,*) '  ***************************  '
215  WRITE(lunout,*) '  ***  grilles_gcm_netcdf ***  '
216  WRITE(lunout,*) '  ***************************  '
217  WRITE(lunout,'(//)')
218  CALL grilles_gcm_netcdf_sub(masque,phis)
219
220#ifdef CPP_PARA
[1319]221  END IF
[2336]222#endif
[1319]223
224END PROGRAM ce0l
[2336]225!
226!-------------------------------------------------------------------------------
Note: See TracBrowser for help on using the repository browser.