source: trunk/LMDZ.COMMON/libf/evolution/nb_time_step_GCM.F90 @ 2840

Last change on this file since 2840 was 2835, checked in by romain.vande, 3 years ago

Mars PEM:
Introduction of the possibility to follow an orbital forcing.
Introduction of new control parameters.
Cleaning of the PEM (removing unused files, add comments and new files)

A file named run_PEM.def can be added to the run.def. It contains the following variables:

_ evol_orbit_pem: Boolean. Do you want to follow an orbital forcing predefined (read in ob_ex_lsp.asc for example)? (default=false)
_ year_bp_ini: Integer. Number of year before present to start the pem run if evol_orbit_pem=.true. , default=0
_ Max_iter_pem: Integer. Maximal number of iteration if none of the stopping criterion is reached and if evol_orbit_pem=.false., default=99999999
_ dt_pem: Integer. Time step of the PEM in year, default=1
_ alpha_criterion: Real. Acceptance rate of sublimating ice surface change, default=0.2
_ soil_pem: Boolean. Do you want to run with subsurface physical processes in the PEM? default=.true.

RV

File size: 2.6 KB
Line 
1!
2! $Id $
3!
4SUBROUTINE nb_time_step_GCM(fichnom,timelen)
5
6      use netcdf, only: nf90_open,NF90_NOWRITE,nf90_noerr,nf90_strerror, &
7                        nf90_get_var, nf90_inq_varid, nf90_inq_dimid, &
8                        nf90_inquire_dimension,nf90_close
9
10      IMPLICIT NONE
11
12!=======================================================================
13!
14! Read initial confitions file
15!
16!=======================================================================
17
18  include "dimensions.h"
19
20!===============================================================================
21! Arguments:
22  CHARACTER(LEN=*), INTENT(IN) :: fichnom          !--- FILE NAME
23!===============================================================================
24!   Local Variables
25  CHARACTER(LEN=256) :: msg, var, modname
26  INTEGER :: iq, fID, vID, idecal
27  INTEGER :: ierr
28
29  INTEGER :: timelen ! number of times stored in the file
30!-----------------------------------------------------------------------
31  modname="nb_time_step_GCM"
32
33!  Open initial state NetCDF file
34  var=fichnom
35  CALL err(NF90_OPEN(var,NF90_NOWRITE,fID),"open",var)
36
37      ierr = nf90_inq_varid (fID, "temps", vID)
38      IF (ierr .NE. nf90_noerr) THEN
39        write(*,*)"read_data_GCM: Le champ <temps> est absent"
40        write(*,*)"read_data_GCM: J essaie <Time>"
41        ierr = nf90_inq_varid (fID, "Time", vID)
42        IF (ierr .NE. nf90_noerr) THEN
43           write(*,*)"read_data_GCM: Le champ <Time> est absent"
44           write(*,*)trim(nf90_strerror(ierr))
45           CALL ABORT_gcm("read_data_GCM", "", 1)
46        ENDIF
47        ! Get the length of the "Time" dimension
48        ierr = nf90_inq_dimid(fID,"Time",vID)
49        ierr = nf90_inquire_dimension(fID,vID,len=timelen)
50      ELSE   
51        ! Get the length of the "temps" dimension
52        ierr = nf90_inq_dimid(fID,"temps",vID)
53        ierr = nf90_inquire_dimension(fID,vID,len=timelen)
54      ENDIF
55
56  CALL err(NF90_CLOSE(fID),"close",fichnom)
57
58  print *, "The number of timestep of the PCM run data=", timelen
59
60  CONTAINS
61
62
63SUBROUTINE err(ierr,typ,nam)
64  INTEGER,          INTENT(IN) :: ierr   !--- NetCDF ERROR CODE
65  CHARACTER(LEN=*), INTENT(IN) :: typ    !--- TYPE OF OPERATION
66  CHARACTER(LEN=*), INTENT(IN) :: nam    !--- FIELD/FILE NAME
67  IF(ierr==NF90_NoERR) RETURN
68  SELECT CASE(typ)
69    CASE('inq');   msg="Field <"//TRIM(nam)//"> is missing"
70    CASE('get');   msg="Reading failed for <"//TRIM(nam)//">"
71    CASE('open');  msg="File opening failed for <"//TRIM(nam)//">"
72    CASE('close'); msg="File closing failed for <"//TRIM(nam)//">"
73  END SELECT
74  CALL ABORT_gcm(TRIM(modname),TRIM(msg),ierr)
75END SUBROUTINE err
76
77END SUBROUTINE nb_time_step_GCM
Note: See TracBrowser for help on using the repository browser.