SURFEX v8.1
General documentation of Surfex
write_header_mnh.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 write_header_mnh
7 ! #############################################################
8 !
9 !!**** * - routine to header-type fields in a lfi file to emulate a MesoNH file
10 !!
11 !! PURPOSE
12 !! -------
13 !
14 !
15 !!** METHOD
16 !! ------
17 !!
18 !! EXTERNAL
19 !! --------
20 !!
21 !!
22 !!
23 !! IMPLICIT ARGUMENTS
24 !! ------------------
25 !!
26 !!
27 !! REFERENCE
28 !! ---------
29 !!
30 !!
31 !! AUTHOR
32 !! ------
33 !!
34 !! V. Masson *METEO-FRANCE*
35 !!
36 !! MODIFICATIONS
37 !! -------------
38 !!
39 !! original 21/05/08
40 !----------------------------------------------------------------------------
41 !
42 !* 0. DECLARATIONS
43 ! ------------
44 !
45 #ifdef SFX_LFI
46 USE modi_fmwrit
47 #endif
48 !
50 !
51 !
52 USE yomhook ,ONLY : lhook, dr_hook
53 USE parkind1 ,ONLY : jprb
54 !
55 IMPLICIT NONE
56 !
57 !* 0.1 Declarations of arguments
58 !
59 !* 0.2 Declarations of local variables
60 !
61  CHARACTER(LEN=100) :: YCOMMENT=' '
62 INTEGER :: IRESP
63 INTEGER :: INB ! number of articles in the file
64  CHARACTER(LEN=28) :: YNAME
65  CHARACTER(LEN=10) :: YBIBUSER =' '
66 REAL(KIND=JPRB) :: ZHOOK_HANDLE
67 !----------------------------------------------------------------------------
68 !
69 IF (lhook) CALL dr_hook('WRITE_HEADER_MNH',0,zhook_handle)
70 #ifdef SFX_LFI
71  CALL fmopen(cfileout_lfi,'UNKNOWN',cluout_lfi,0,1,1,inb,iresp)
72 !
73  CALL fmwritn0(cfileout_lfi,'MASDEV',cluout_lfi,1,47,4,100,ycomment,iresp)
74  CALL fmwritn0(cfileout_lfi,'BUGFIX',cluout_lfi,1,0,4,100,ycomment,iresp)
75  CALL fmwritc0(cfileout_lfi,'BIBUSER',cluout_lfi,1,ybibuser,4,100,ycomment,iresp)
76 yname=cfileout_lfi
77  CALL fmwritc0(cfileout_lfi,'MY_NAME',cluout_lfi,1,yname,4,100,ycomment,iresp)
78 yname=' '
79  CALL fmwritc0(cfileout_lfi,'DAD_NAME',cluout_lfi,1,yname,4,100,ycomment,iresp)
80  CALL fmwritc0(cfileout_lfi,'PROGRAM',cluout_lfi,1,'SURFEX',4,100,ycomment,iresp)
81  CALL fmwritn0(cfileout_lfi,'KMAX',cluout_lfi,1,0,4,100,ycomment,iresp)
82  CALL fmwritc0(cfileout_lfi,'STORAGE_TYPE',cluout_lfi,1,'SU',4,100,ycomment,iresp)
83  CALL fmwritl0(cfileout_lfi,'CARTESIAN ',cluout_lfi,1,lcartesian,4,100,ycomment,iresp)
84  CALL fmwritl0(cfileout_lfi,'THINSHELL ',cluout_lfi,1,.true.,4,100,ycomment,iresp)
85 !
86  CALL fmclos(cfileout_lfi,'KEEP',cluout_lfi,iresp)
87 #endif
88 IF (lhook) CALL dr_hook('WRITE_HEADER_MNH',1,zhook_handle)
89 !
90 !-------------------------------------------------------------------------------
91 END SUBROUTINE write_header_mnh
subroutine fmopen(HFILEM, HSTATU, HFIPRI, KNPRAR, KFTYPE, KVERB, KNINAR, KRESP)
Definition: fmopen.F90:4
subroutine write_header_mnh
character(len=28), save cluout_lfi
subroutine fmclos(HFILEM, HSTATU, HFIPRI, KRESP)
Definition: fmclos.F90:3
integer, parameter jprb
Definition: parkind1.F90:32
subroutine fmwritn0(HFILEM, HRECFM, HFIPRI, KLENG, KFIELD, KGRID, KLENCH, HCOMMENT, KRESP)
Definition: fmwritn0.F90:4
logical lhook
Definition: yomhook.F90:15
character(len=28), save cfileout_lfi
subroutine fmwritc0(HFILEM, HRECFM, HFIPRI, KLENG, HFIELD, KGRID, KLENCH, HCOMMENT, KRESP)
Definition: fmwritc0.F90:4
subroutine fmwritl0(HFILEM, HRECFM, HFIPRI, KLENG, OFIELD, KGRID, KLENCH, HCOMMENT, KRESP)
Definition: fmwritl0.F90:4