SURFEX v8.1
General documentation of Surfex
write_file_vecmap.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  SUBROUTINE write_file_vecmap(PVAR,HVAR,KCAT)
8 ! ##########################
9 !
10 !!
11 !! PURPOSE
12 !! -------
13 !
14 !
15 !!** METHOD
16 !! ------
17 !
18 !! EXTERNAL
19 !! --------
20 !!
21 !! none
22 !!
23 !! IMPLICIT ARGUMENTS
24 !! ------------------
25 !!
26 !! REFERENCE
27 !! ---------
28 !!
29 !! AUTHOR
30 !! ------
31 !!
32 !! K. Chancibault * Meteo-France *
33 !!
34 !! MODIFICATIONS
35 !! -------------
36 !!
37 !! Original 25/01/2005
38 !-------------------------------------------------------------------------------
39 !
40 !* 0. DECLARATIONS
41 ! ------------
42 !
43 USE modd_topd_par, ONLY : nunit
44 USE modd_topodyn
45 !
46 USE modd_surf_par, ONLY:xundef
47 USE modi_open_file
48 USE modi_close_file
49 !
50 USE yomhook ,ONLY : lhook, dr_hook
51 USE parkind1 ,ONLY : jprb
52 !
53 IMPLICIT NONE
54 !
55 !* 0.1 declarations of arguments
56 !
57 REAL, DIMENSION(:),INTENT(IN) :: PVAR ! variable to write in the file
58  CHARACTER(LEN=30), INTENT(IN) :: HVAR ! end name of the file
59 INTEGER, INTENT(IN) :: KCAT ! catchment number
60 !
61 !* 0.2 declarations of local variables
62 !
63  CHARACTER(LEN=50) :: CNAME
64  CHARACTER(LEN=40) :: CFMT
65 INTEGER :: JJ,JI,JK
66 INTEGER :: IINDEX ! reference number of the pixel
67 REAL :: ZOUT ! pixel not included in the catchment
68 REAL :: ZMIN,ZMAX
69 REAL(KIND=JPRB) :: ZHOOK_HANDLE
70 !-------------------------------------------------------------------------------
71 IF (lhook) CALL dr_hook('WRITE_FILE_VECMAP',0,zhook_handle)
72 !
73 !* 0. Initialization:
74 ! ---------------
75 !
76 zout = xundef
77 zmin = minval(pvar)
78 zmax = maxval(pvar)
79 !
80 CNAME = TRIM(CCAT(KCAT))//TRIM(HVAR)
81 !
82  CALL open_file('ASCII ',nunit,hfile=cname,hform='FORMATTED')
83 !
84 DO ji=1,5
85  WRITE(nunit,*)
86 ENDDO
87 !
88 WRITE(nunit,*) xx0(kcat)
89 WRITE(nunit,*) xy0(kcat)
90 WRITE(nunit,*) nnxc(kcat)
91 WRITE(nunit,*) nnyc(kcat)
92 WRITE(nunit,*) zout
93 WRITE(nunit,*) xdxt(kcat)
94 WRITE(nunit,*) zmin
95 WRITE(nunit,*) zmax
96 !
97 DO ji=1,nnyc(kcat)
98  DO jk=1,nnxc(kcat)
99  iindex = (ji - 1) * nnxc(kcat) + jk
100  IF (xtopd(kcat,iindex).EQ.xnul(kcat)) THEN
101  WRITE(nunit,*) zout
102  ELSE
103  WRITE(nunit,*) pvar(nline(kcat,iindex))
104  ENDIF
105  ENDDO
106 ENDDO
107 !
108  CALL close_file('ASCII ',nunit)
109 !
110 IF (lhook) CALL dr_hook('WRITE_FILE_VECMAP',1,zhook_handle)
111 !
112 END SUBROUTINE write_file_vecmap
113 
real, dimension(:,:), allocatable xtopd
subroutine open_file(HPROGRAM, KUNIT, HFILE, HFORM, HACTION, HACCESS, KR
Definition: open_file.F90:7
real, dimension(:), allocatable xx0
subroutine write_file_vecmap(PVAR, HVAR, KCAT)
integer, dimension(:,:), allocatable nline
real, parameter xundef
integer, parameter jprb
Definition: parkind1.F90:32
real, dimension(:), allocatable xdxt
subroutine close_file(HPROGRAM, KUNIT)
Definition: close_file.F90:7
integer, dimension(:), allocatable nnyc
real, dimension(:), allocatable xnul
logical lhook
Definition: yomhook.F90:15
integer, dimension(:), allocatable nnxc
real, dimension(:), allocatable xy0