SURFEX v8.1
General documentation of Surfex
fmwritc0.F90
Go to the documentation of this file.
1 ! ######spl
2  SUBROUTINE fmwritc0(HFILEM,HRECFM,HFIPRI,KLENG,HFIELD,KGRID,&
3  KLENCH,HCOMMENT,KRESP)
4  USE parkind1, ONLY : jprb
5  USE yomhook , ONLY : lhook, dr_hook
6 ! #############################################################
7 !
8 !!**** *FMWRITC0* - routine to write a string scalar into a "FM"-file
9 !!
10 !! PURPOSE
11 !! -------
12 !
13 ! The purpose of FMWRITL0 is to convert the string into arrayr of
14 ! integer(kind=8) and to call FM_WRIT without interface module
15 !
16 !!** METHOD
17 !! ------
18 !!
19 !! EXTERNAL
20 !! --------
21 !!
22 !! FM_WRIT
23 !!
24 !! IMPLICIT ARGUMENTS
25 !! ------------------
26 !!
27 !!
28 !! REFERENCE
29 !! ---------
30 !!
31 !!
32 !! AUTHOR
33 !! ------
34 !!
35 !! V. MASSON *METEO-FRANCE*
36 !!
37 !! MODIFICATIONS
38 !! -------------
39 !!
40 !! original 06/08/97
41 !----------------------------------------------------------------------------
42 !
43 !* 0. DECLARATIONS
44 ! ------------
45 !
46 IMPLICIT NONE
47 !
48 !* 0.1 Declarations of arguments
49 !
50 CHARACTER(LEN=*) ,INTENT(IN) ::HFILEM ! file name
51 CHARACTER(LEN=*) ,INTENT(IN) ::HRECFM ! name of the article to be written
52 
53 CHARACTER(LEN=*) ,INTENT(IN) ::HFIPRI ! file for prints in FM
54 
55 INTEGER, INTENT(IN) ::KLENG ! length of the data field
56 CHARACTER(LEN=*), &
57  INTENT(IN) ::hfield ! array containing the data field
58 INTEGER, INTENT(IN) ::KGRID ! C-grid indicator (u,v,w,T)
59 INTEGER, INTENT(IN) ::KLENCH ! length of comment string
60 
61 CHARACTER(LEN=*) ,INTENT(IN) ::HCOMMENT ! comment string
62 
63 INTEGER, INTENT(OUT)::KRESP ! return-code if problems araised
64 !
65 !* 0.2 Declarations of local variables
66 !
67 INTEGER :: JLOOP
68 INTEGER(KIND=8), DIMENSION(:), ALLOCATABLE :: IFIELD
69 INTEGER :: ILENG
70 !-------------------------------------------------------------------------------
71 !
72 REAL(KIND=JPRB) :: ZHOOK_HANDLE
73 IF (lhook) CALL dr_hook('FMWRITC0',0,zhook_handle)
74 ileng=len(hfield)
75 ALLOCATE(ifield(ileng))
76 DO jloop=1,ileng
77  ifield(jloop)=iachar(hfield(jloop:jloop))
78 END DO
79 !
80 CALL FM_WRIT(HFILEM,HRECFM,HFIPRI,ILENG,IFIELD,KGRID,KLENCH,HCOMMENT,KRESP)
81 !
82 DEALLOCATE(ifield)
83 !-------------------------------------------------------------------------------
84 IF (lhook) CALL dr_hook('FMWRITC0',1,zhook_handle)
85 END SUBROUTINE fmwritc0
integer, parameter jprb
Definition: parkind1.F90:32
logical lhook
Definition: yomhook.F90:15
subroutine fmwritc0(HFILEM, HRECFM, HFIPRI, KLENG, HFIELD, KGRID, KLENCH, HCOMMENT, KRESP)
Definition: fmwritc0.F90:4