SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
pgd_snap_temp_profile.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  SUBROUTINE pgd_snap_temp_profile(HPROGRAM,HFILENAME,PSNAP_COEF, &
7  ksnap,ktps,hsnap_time_ref )
8 ! ##############################################################
9 !
10 !!**** *PGD_SNAP_TEMP_PROFILE* reads a temporal emission profile
11 !!
12 !! PURPOSE
13 !! -------
14 !!
15 !! AUTHOR
16 !! ------
17 !!
18 !! S. QUEGUINER Meteo-France
19 !!
20 !! MODIFICATION
21 !! ------------
22 !!
23 !! Original 09/2011
24 !! A. Alias 07/2013 CONTINUE procedure for compilation on beaufix
25 !!
26 !----------------------------------------------------------------------------
27 !
28 !* 0. DECLARATION
29 ! -----------
30 !
31 
32 USE modi_open_file
33 USE modi_close_file
34 USE modi_get_luout
36 !
37 !
38 USE modd_surf_par, ONLY : xundef
39 USE yomhook ,ONLY : lhook, dr_hook
40 USE parkind1 ,ONLY : jprb
41 IMPLICIT NONE
42 !
43 !* 0.1 Declaration of arguments
44 ! ------------------------
45 !
46  CHARACTER(LEN=6), INTENT(IN) :: hprogram ! Type of program
47  CHARACTER(LEN=28), INTENT(IN) :: hfilename ! Name of the field file.
48 REAL, DIMENSION(:,:), INTENT(OUT):: psnap_coef ! Snap coefficient
49 INTEGER, INTENT(IN) :: ktps ! Number of time step
50 INTEGER, INTENT(IN) :: ksnap ! Number of snaps
51  CHARACTER(LEN=5), OPTIONAL, INTENT(OUT):: hsnap_time_ref ! Reference time
52 ! ! 'UTC ' : UTC time
53 ! ! 'SOLAR' : SOLAR time
54 ! ! 'LEGAL' : LEGAL time
55 !
56 !* 0.2 Declaration of local variables
57 ! ------------------------------
58 !
59 INTEGER :: iunit ! logical unit
60 INTEGER :: jsnap ! loop counter on snaps
61  CHARACTER(LEN=200) :: ycomment
62 REAL, DIMENSION(KTPS) :: zsnap_coef ! snap temporal coefficient
63 INTEGER :: isnap ! snap number
64 INTEGER :: iluout ! output listing
65 REAL(KIND=JPRB) :: zhook_handle
66 !----------------------------------------------------------------------------
67 !
68 !* 1. Open the file
69 ! -------------
70 !
71 IF (lhook) CALL dr_hook('PGD_SNAP_TEMP_PROFILE',0,zhook_handle)
72 !
73  CALL open_file(hprogram,iunit,hfilename,'FORMATTED',haction='READ')
74 !
75  CALL get_luout(hprogram,iluout)
76 !
77 !----------------------------------------------------------------------------
78 READ(iunit,'(A)') ycomment
79 !----------------------------------------------------------------------------
80 !
81 !* 2. Reading of time reference for hourly profiles
82 ! ---------------------------------------------
83 !
84 IF (present(hsnap_time_ref)) THEN
85  READ(iunit,'(A)') hsnap_time_ref
86  CALL test_nam_var_surf(iluout,'CSNAP_TIME_REF',hsnap_time_ref,'UTC ','SOLAR','LEGAL')
87 END IF
88 !
89 !----------------------------------------------------------------------------
90 READ(iunit,'(A)') ycomment
91 !----------------------------------------------------------------------------
92 !
93 !* 3. Reading of snaps temporal coefficients
94 ! --------------------------------------
95 !
96 psnap_coef(:,:)=0.
97 !
98 DO jsnap=1,ksnap
99  READ(iunit,*,end=2000) isnap,zsnap_coef(1:ktps)
100  psnap_coef(:,isnap)=zsnap_coef(:)
101 ENDDO
102 !
103 !----------------------------------------------------------------------------
104 !
105 !* 8. Closing of the data file
106 ! ------------------------
107 !
108 2000 CONTINUE
109  CALL close_file(hprogram,iunit)
110 !
111 IF (lhook) CALL dr_hook('PGD_SNAP_TEMP_PROFILE',1,zhook_handle)
112 !
113 !-------------------------------------------------------------------------------
114 !
115 END SUBROUTINE pgd_snap_temp_profile
subroutine pgd_snap_temp_profile(HPROGRAM, HFILENAME, PSNAP_COEF, KSNAP, KTPS, HSNAP_TIME_REF)
subroutine close_file(HPROGRAM, KUNIT)
Definition: close_file.F90:6
subroutine get_luout(HPROGRAM, KLUOUT)
Definition: get_luout.F90:6
subroutine open_file(HPROGRAM, KUNIT, HFILE, HFORM, HACTION, HACCESS, KRECL)
Definition: open_file.F90:6