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

Last change on this file since 2841 was 2841, checked in by romain.vande, 2 years ago

Mars PEM:
PEM is now adapted to run with XIOS diurnal averages (when they will work properly)
RV

File size: 3.0 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_counter>"
41        ierr = nf90_inq_varid (fID, "time_counter", vID)
42        IF (ierr .NE. nf90_noerr) THEN
43          write(*,*)"read_data_GCM: Le champ <time_counter> est absent"
44          write(*,*)"read_data_GCM: J essaie <Time>"
45          IF (ierr .NE. nf90_noerr) THEN
46            write(*,*)"read_data_GCM: Le champ <Time> est absent"
47            write(*,*)trim(nf90_strerror(ierr))
48            CALL ABORT_gcm("read_data_GCM", "", 1)
49          ENDIF
50          ! Get the length of the "Time" dimension
51          ierr = nf90_inq_dimid(fID,"Time",vID)
52          ierr = nf90_inquire_dimension(fID,vID,len=timelen)         
53        ENDIF
54        ! Get the length of the "time_counter" dimension
55        ierr = nf90_inq_dimid(fID,"time_counter",vID)
56        ierr = nf90_inquire_dimension(fID,vID,len=timelen)
57      ELSE   
58        ! Get the length of the "temps" dimension
59        ierr = nf90_inq_dimid(fID,"temps",vID)
60        ierr = nf90_inquire_dimension(fID,vID,len=timelen)
61      ENDIF
62
63  CALL err(NF90_CLOSE(fID),"close",fichnom)
64
65  print *, "The number of timestep of the PCM run data=", timelen
66
67  CONTAINS
68
69SUBROUTINE err(ierr,typ,nam)
70  INTEGER,          INTENT(IN) :: ierr   !--- NetCDF ERROR CODE
71  CHARACTER(LEN=*), INTENT(IN) :: typ    !--- TYPE OF OPERATION
72  CHARACTER(LEN=*), INTENT(IN) :: nam    !--- FIELD/FILE NAME
73  IF(ierr==NF90_NoERR) RETURN
74  SELECT CASE(typ)
75    CASE('inq');   msg="Field <"//TRIM(nam)//"> is missing"
76    CASE('get');   msg="Reading failed for <"//TRIM(nam)//">"
77    CASE('open');  msg="File opening failed for <"//TRIM(nam)//">"
78    CASE('close'); msg="File closing failed for <"//TRIM(nam)//">"
79  END SELECT
80  CALL ABORT_gcm(TRIM(modname),TRIM(msg),ierr)
81END SUBROUTINE err
82
83END SUBROUTINE nb_time_step_GCM
Note: See TracBrowser for help on using the repository browser.