SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
writesurf_dummyn.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 writesurf_dummy_n (DGU, U, &
7  duu, &
8  hprogram)
9 ! ##########################################
10 !
11 !!**** *WRITESURF_DUMMY_n* - routine to write dummy surface fields
12 !!
13 !! PURPOSE
14 !! -------
15 !!
16 !! AUTHOR
17 !! ------
18 !! V. Masson *Meteo France*
19 !!
20 !! MODIFICATIONS
21 !! -------------
22 !! Original 03/2004
23 !! P.Tulet 2015 Bug depassement de tableau YRECFM
24 !-------------------------------------------------------------------------------
25 !
26 !* 0. DECLARATIONS
27 ! ------------
28 !
29 !
30 !
31 !
32 !
34 USE modd_surf_atm_n, ONLY : surf_atm_t
35 !
37 !
39 !
40 !
41 USE yomhook ,ONLY : lhook, dr_hook
42 USE parkind1 ,ONLY : jprb
43 !
44 IMPLICIT NONE
45 !
46 !* 0.1 Declarations of arguments
47 ! -------------------------
48 !
49 !
50 !
51 TYPE(diag_surf_atm_t), INTENT(INOUT) :: dgu
52 TYPE(surf_atm_t), INTENT(INOUT) :: u
53 !
54 TYPE(dummy_surf_fields_t), INTENT(INOUT) :: duu
55 !
56  CHARACTER(LEN=6), INTENT(IN) :: hprogram !
57 !
58 !* 0.2 Declarations of local variables
59 ! -------------------------------
60 !
61 INTEGER :: jdummy ! loop counter
62 !
63  CHARACTER(LEN=20 ):: ystring20 ! string
64  CHARACTER(LEN=3 ):: ystring03 ! string
65 !
66 INTEGER :: iresp ! IRESP : return-code if a problem appears
67  CHARACTER(LEN=12) :: yrecfm ! Name of the article to be read
68  CHARACTER(LEN=100):: ycomment ! Comment string
69 REAL(KIND=JPRB) :: zhook_handle
70 !
71 !-------------------------------------------------------------------------------
72 !
73 !* 1. Number of dummy fields :
74 ! ----------------------
75 !
76 IF (lhook) CALL dr_hook('WRITESURF_DUMMY_N',0,zhook_handle)
77 yrecfm='DUMMY_GR_NBR'
78 ycomment=' '
79 !
80  CALL write_surf(dgu, u, &
81  hprogram,yrecfm,duu%NDUMMY_NBR,iresp,hcomment=ycomment)
82 !
83 !-------------------------------------------------------------------------------
84 !
85 !* 2. Dummy fields :
86 ! ------------
87 !
88 DO jdummy=1,duu%NDUMMY_NBR
89  !
90  WRITE(yrecfm,'(A8,I3.3,A1)') 'DUMMY_GR',jdummy,' '
91  ystring20=duu%CDUMMY_NAME(jdummy)
92  ystring03=duu%CDUMMY_AREA(jdummy)
93  ycomment='X_Y_'//yrecfm//ystring20//ystring03// &
94  ' '
95  CALL write_surf(dgu, u, &
96  hprogram,yrecfm,duu%XDUMMY_FIELDS(:,jdummy),iresp,hcomment=ycomment)
97 END DO
98 IF (lhook) CALL dr_hook('WRITESURF_DUMMY_N',1,zhook_handle)
99 !
100 !-------------------------------------------------------------------------------
101 !
102 END SUBROUTINE writesurf_dummy_n
subroutine writesurf_dummy_n(DGU, U, DUU, HPROGRAM)