SURFEX v8.1
General documentation of Surfex
fmlook.F90
Go to the documentation of this file.
1 ! ######spl
2  SUBROUTINE fmlook(HFILEM,HFIPRI,KNUMBR,KRESP)
3  USE parkind1, ONLY : jprb
4  USE yomhook , ONLY : lhook, dr_hook
5 ! #############################################
6 !
7 !!**** *FMLOOK* - routine to look for the logical unit attributed to a file
8 !!
9 !! PURPOSE
10 !! -------
11 !
12 ! The purpose of FMLOOK is to look for the logical unit (Fortran)
13 ! that is associated to the file named HFILEM. This unit was attributed
14 ! previously to HFILEM by FMATTR.
15 !
16 !!** METHOD
17 !! ------
18 !!
19 !! The string HFILEM is searched in array CNAMFI which contains the
20 !! names of all files that have been opened for the FM-routines.
21 !! The place in array CNAMFI of HFILEM corresponds exactly to
22 !! its logical unit.
23 !!
24 !! EXTERNAL
25 !! --------
26 !!
27 !! NONE
28 !!
29 !! IMPLICIT ARGUMENTS
30 !! ------------------
31 !!
32 !! MODULE: MODD_FMDECLAR contains management parameters and
33 !! storage arrays to move information around at the
34 !! level of all "FM"-routines.
35 !!
36 !! REFERENCE
37 !! ---------
38 !!
39 !! see the Technical Specifications Report for the Meso-nh project
40 !! (in French)
41 !!
42 !! AUTHOR
43 !! ------
44 !!
45 !! C. FISCHER *METEO-FRANCE*
46 !!
47 !! MODIFICATIONS
48 !! -------------
49 !!
50 !! original 04/94
51 !!
52 !----------------------------------------------------------------------------
53 !
54 !* 0. DECLARATIONS
55 ! ------------
56 !
57 USE modd_fmdeclar
58 
59 IMPLICIT NONE
60 !
61 !* 0.1 Declarations of arguments
62 !
63 CHARACTER(LEN=*), INTENT(IN) ::HFILEM ! file name
64 
65 CHARACTER(LEN=*), INTENT(IN) ::HFIPRI ! file for prints in FM
66 
67 INTEGER, INTENT(OUT)::KNUMBR ! logical unit number
68 INTEGER, INTENT(OUT)::KRESP ! return-code if problems araised
69 
70 !
71 !* 0.2 Declarations of local variables
72 !
73 INTEGER::J,ILOGIQ=0,iresp=0,ilupri
74 CHARACTER(LEN=JPFINL)::YLOCFN
75 !
76 !* 0.3 Taskcommon for logical units
77 !
78 COMMON/TASKLOOK/ILUPRI
79 !DIR$ TASKCOMMON TASKLOOK
80 !
81 !----------------------------------------------------------------------------
82 !
83 !* 1. WE LOOK FOR THE FILE NAME IN ARRAY CNAMFI
84 !
85 REAL(KIND=JPRB) :: ZHOOK_HANDLE
86 IF (lhook) CALL dr_hook('FMLOOK',0,zhook_handle)
87 ilogiq = 0 ; iresp = 0 ; ilupri = 6
88 IF (nopefi.LT.1) THEN
89  iresp=-53
90  GOTO 1000
91 ENDIF
92 ylocfn=hfilem ; ylocfn=adjustl(ylocfn)
93 DO j=1,jpnxlu
94  IF (ylocfn.EQ.cnamfi(j)) THEN
95  ilogiq=j
96  EXIT
97  ENDIF
98 ENDDO
99 IF (ilogiq.EQ.0) THEN
100  iresp=-54
101  GOTO 1000
102 ENDIF
103 
104 knumbr=ilogiq
105 !
106 !* 2. MESSAGE PRINTING WHATEVER THE ISSUE WAS
107 !
108 1000 CONTINUE
109 
110 IF (iresp.NE.0) THEN
111 ylocfn=adjustl(hfipri)
112 DO j=1,jpnxlu
113  IF (cnamfi(j).EQ.ylocfn) THEN
114  ilupri=j
115  EXIT
116  ENDIF
117 ENDDO
118 WRITE (ilupri,*) ' exit from FMLOOK with IRESP:',iresp
119 WRITE (ilupri,*) ' | HFILEM = ',hfilem
120 ENDIF
121 kresp=iresp
122 
123 IF (lhook) CALL dr_hook('FMLOOK',1,zhook_handle)
124 RETURN
125  IF (lhook) CALL dr_hook('FMLOOK',1,zhook_handle)
126  END SUBROUTINE fmlook
subroutine fmlook(HFILEM, HFIPRI, KNUMBR, KRESP)
Definition: fmlook.F90:3
integer, parameter jpnxlu
integer, parameter jprb
Definition: parkind1.F90:32
logical lhook
Definition: yomhook.F90:15