SURFEX v8.1
General documentation of Surfex
trip_change_date.F90
Go to the documentation of this file.
1 !#########
3 !############################################
4 !
5 !!**** *TRIP_CHANGE_DATE*
6 !!
7 !! PURPOSE
8 !! -------
9 !
10 ! Change the current date in the TRIP restart.
11 ! Important for spin up procedure
12 !
13 !!
14 !! AUTHOR
15 !! ------
16 !! B. Decharme
17 !!
18 !! MODIFICATIONS
19 !! -------------
20 !! Original 01/14
21 !-------------------------------------------------------------------------------
22 !
23 !* 0. DECLARATIONS
24 ! ------------
25 !
26 USE modd_trip_par, ONLY : lncprint
27 !
28 USE netcdf
30 !
31 USE modi_init_trip_par
32 !
33 USE yomhook ,ONLY : lhook, dr_hook
34 USE parkind1 ,ONLY : jprb
35 !
36 IMPLICIT NONE
37 !
38 !* 0.1 declarations of local variables
39 !
40  CHARACTER(LEN=NF90_MAX_NAME), PARAMETER :: YFILE = 'TRIP_RESTART.nc'
41  CHARACTER(LEN=NF90_MAX_NAME), PARAMETER :: YDATE = 'date'
42 INTEGER, PARAMETER :: ILISTING = 6
43 LOGICAL, PARAMETER :: LRW = .true.
44 !
45 REAL*4, DIMENSION(4) :: ZDATE_OLD, ZDATE
46 REAL, DIMENSION(4) :: ZREAD
47 !
48 INTEGER :: IYEAR
49 INTEGER :: IMONTH
50 INTEGER :: IDAY
51 INTEGER :: ITIME
52 !
53 INTEGER :: IC, IDATEID, INCID
54 !
55 REAL(KIND=JPRB) :: ZHOOK_HANDLE
56 !
57 !-------------------------------------------------------------------------------
58 !
59 IF (lhook) CALL dr_hook('TRIP_CHANGE_DATE',0,zhook_handle)
60 !
61 !-------------------------------------------------------------------------------
62  CALL init_trip_par
63 !-------------------------------------------------------------------------------
64 !
65 ! * Read current date
66 !
67 OPEN(unit=21, file='date_trip', form='formatted')
68 READ(21, *) iyear, imonth, iday, itime
69  CLOSE(21)
70 !
71 zdate(1) = REAL(iyear)
72 zdate(2) = REAL(imonth)
73 zdate(3) = REAL(iday)
74 zdate(4) = REAL(itime)
75 !
76 ! * Open netcdf file
77 !
78  CALL ncopen(ilisting,lrw,lncprint,yfile,incid)
79 !
80 ! * read date in restart file
81 !
82  CALL ncread(ilisting,incid,ydate,zread(:),lncprint)
83 zdate_old(:) = zread(:)
84 !
85 WRITE(ilisting,*)'Change date in trip restart :'
86 WRITE(ilisting,*)'Year :',int(zdate_old(1)),'to',iyear
87 WRITE(ilisting,*)'Month :',int(zdate_old(2)),'to',imonth
88 WRITE(ilisting,*)'Day :',int(zdate_old(3)),'to',iday
89 WRITE(ilisting,*)'Time :',int(zdate_old(4)),'to',itime
90 
91 ! * Write current date in restart file
92 !
93 ic = nf90_inq_varid(incid,ydate,idateid)
94 IF(ic/=nf90_noerr)THEN
95  WRITE(ilisting,*)'TRIP_CHANGE_DATE: NF90_INQ_VARID problem'
96  stop
97 ENDIF
98 !
99 ic = nf90_put_var(incid,idateid,zdate)
100 IF(ic/=nf90_noerr)THEN
101  WRITE(ilisting,*)'TRIP_CHANGE_DATE: NF90_PUT_VAR problem'
102  stop
103 ENDIF
104 !
105 WRITE(ilisting,*)'Sucess in writting current date'
106 !
107 ! * Close netcdf file
108 !
109  CALL ncclose(ilisting,lncprint,yfile,incid)
110 !
111 IF (lhook) CALL dr_hook('TRIP_CHANGE_DATE',1,zhook_handle)
112 !
113 !-------------------------------------------------------------------------------
114 END PROGRAM trip_change_date
subroutine init_trip_par
integer, parameter jprb
Definition: parkind1.F90:32
logical, save lncprint
subroutine ncclose(KLISTING, OVERBOSE, HFILENAME, KNCID)
logical lhook
Definition: yomhook.F90:15
program trip_change_date
subroutine ncopen(KLISTING, ORW, OVERBOSE, HFILENAME, KNCID)