SURFEX v8.1
General documentation of Surfex
write_discharge_file.F90
Go to the documentation of this file.
1 !SFX_LIC Copyright 1994-2014 CNRS, Meteo-France and Universite Paul Sabatier
2 !SFX_LIC This is part of the SURFEX software governed by the CeCILL-C licence
3 !SFX_LIC version 1. See LICENSE, CeCILL-C_V1-en.txt and CeCILL-C_V1-fr.txt
4 !SFX_LIC for details. version 1.
5 !-----------------------------------------------------------------
6 ! #######################
7 !
8  SUBROUTINE write_discharge_file(HPROGRAM,HFILE,HFORM,&
9  KYEAR,KMONTH,KDAY,KH,KM,PQTOT)
10 ! #######################
11 !
12 !!**** *WRITE_DISCHARGE_FILE*
13 !!
14 !! PURPOSE
15 !! -------
16 ! This routine aims at reading topographic files
17 !!** METHOD
18 !! ------
19 !
20 !! EXTERNAL
21 !! --------
22 !!
23 !! none
24 !!
25 !! IMPLICIT ARGUMENTS
26 !! ------------------
27 !!
28 !!
29 !!
30 !!
31 !!
32 !! REFERENCE
33 !! ---------
34 !!
35 !!
36 !!
37 !! AUTHOR
38 !! ------
39 !!
40 !! B. Vincendon * Meteo-France *
41 !!
42 !! MODIFICATIONS
43 !! -------------
44 !!
45 !! Original 11/2006
46 !-------------------------------------------------------------------------------
47 !
48 !* 0. DECLARATIONS
49 ! ------------
50 !
51 USE modd_topd_par, ONLY : nunit
53 !
54 USE modi_get_luout
55 USE modi_open_file
56 USE modi_close_file
57 !
58 USE yomhook ,ONLY : lhook, dr_hook
59 USE parkind1 ,ONLY : jprb
60 !
61 IMPLICIT NONE
62 !
63 !* 0.1 declarations of arguments
64 !
65  CHARACTER(LEN=*), INTENT(IN) :: HPROGRAM !
66  CHARACTER(LEN=*), INTENT(IN) :: HFILE ! File to be read
67  CHARACTER(LEN=*), INTENT(IN) :: HFORM ! Format of the file to be read
68 INTEGER, DIMENSION(:), INTENT(IN) :: KYEAR ! Year of the beginning of the simulation.
69 INTEGER, DIMENSION(:), INTENT(IN) :: KMONTH ! Month of the beginning of the simulation.
70 INTEGER, DIMENSION(:), INTENT(IN) :: KDAY ! Day of the beginning of the simulation.
71 INTEGER, DIMENSION(:), INTENT(IN) :: KH ! Hour of the beginning of the simulation.
72 INTEGER, DIMENSION(:), INTENT(IN) :: KM ! Minutes of the beginning of the simulation.
73 REAL, DIMENSION(:,:) , INTENT(IN) :: PQTOT ! Discharge to be writen
74 !
75 !
76 !* 0.2 declarations of local variables
77 !
78 INTEGER :: JJ,JCAT ! loop control
79 INTEGER :: ILUOUT ! Unit of the files
80 !
81  CHARACTER(LEN=28) :: YFILE
82  CHARACTER(LEN=40) :: YFORM ! Writing format
83 REAL(KIND=JPRB) :: ZHOOK_HANDLE
84 !-------------------------------------------------------------------------------
85 IF (lhook) CALL dr_hook('WRITE_DISCHARGE_FILE',0,zhook_handle)
86 !
87 !* 0.3 preparing file openning
88 ! ----------------------
89 !
90  CALL get_luout(hprogram,iluout)
91 yform='(I4,A1,I2,A1,I2,A1,I2,A1,I2,A1,F7.2)'
92 !
93 DO jcat=1,nncat
94  !
95  yfile = trim(ccat(jcat))//'_'//trim(hfile)
96  !
97  CALL open_file(hprogram,nunit,yfile,hform,haction='WRITE')
98  !
99  WRITE(nunit,*) 'YEAR;MO;DA;HO;MI;',ccat(jcat)
100  DO jj=1,nnb_topd_step
101  WRITE(nunit,yform) kyear(jj),';',kmonth(jj),';',kday(jj),';',&
102  kh(jj) ,';',km(jj) ,';',pqtot(jcat,jj)
103  ENDDO
104  !
105  CALL close_file(hprogram,nunit)
106  !
107 ENDDO
108 !
109 IF (lhook) CALL dr_hook('WRITE_DISCHARGE_FILE',1,zhook_handle)
110 !
111 END SUBROUTINE write_discharge_file
112 
static const char * trim(const char *name, int *n)
Definition: drhook.c:2383
subroutine open_file(HPROGRAM, KUNIT, HFILE, HFORM, HACTION, HACCESS, KR
Definition: open_file.F90:7
character(len=15), dimension(jpcat) ccat
integer nnb_topd_step
integer, parameter jprb
Definition: parkind1.F90:32
subroutine close_file(HPROGRAM, KUNIT)
Definition: close_file.F90:7
subroutine write_discharge_file(HPROGRAM, HFILE, HFORM, KYEAR, KMONTH, KDAY, KH, KM, PQTOT)
subroutine get_luout(HPROGRAM, KLUOUT)
Definition: get_luout.F90:7
logical lhook
Definition: yomhook.F90:15