SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
open_file_nc.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 open_file_nc(KUNIT,HFILE,HFORM,HACTION,HACCESS,KRECL)
7 ! #######################################################
8 !
9 !!**** *OPEN_FILE_NC* - routine to open a file
10 !!
11 !! PURPOSE
12 !! -------
13 !!
14 !!** METHOD
15 !! ------
16 !!
17 !! EXTERNAL
18 !! --------
19 !!
20 !!
21 !! IMPLICIT ARGUMENTS
22 !! ------------------
23 !!
24 !! REFERENCE
25 !! ---------
26 !!
27 !!
28 !! AUTHOR
29 !! ------
30 !! V. Masson *Meteo France*
31 !!
32 !! MODIFICATIONS
33 !! -------------
34 !! Original 01/2003
35 ! 10/2014 : test if file exists for 'read' E. Martin
36 !-------------------------------------------------------------------------------
37 !
38 !* 0. DECLARATIONS
39 ! ------------
40 !
41 USE modd_io_surf_nc, ONLY : cluout_nc
42 !
43 !
44 USE yomhook ,ONLY : lhook, dr_hook
45 USE parkind1 ,ONLY : jprb
46 !
47 USE modi_abor1_sfx
48 !
49 USE modi_get_luout
50 IMPLICIT NONE
51 !
52 !* 0.1 Declarations of arguments
53 ! -------------------------
54 !
55 INTEGER, INTENT(OUT):: kunit ! logical unit
56  CHARACTER(LEN=28), INTENT(IN) :: hfile ! file to open
57  CHARACTER(LEN=11), INTENT(IN) :: hform ! type of file
58  CHARACTER(LEN=9), INTENT(IN) :: haction ! action
59  CHARACTER(LEN=6), INTENT(IN) :: haccess ! access type
60 INTEGER, INTENT(IN) :: krecl ! record length
61 !
62 !* 0.2 Declarations of local variables
63 ! -------------------------------
64 !
65 INTEGER :: iluout
66 INTEGER :: iresp
67 REAL(KIND=JPRB) :: zhook_handle
68 LOGICAL :: lexist
69 
70 !-------------------------------------------------------------------------------
71 !
72 IF (lhook) CALL dr_hook('OPEN_FILE_NC',0,zhook_handle)
73 
74 IF(haction=='READ ') THEN
75  INQUIRE (file=hfile,exist=lexist)
76  IF (.NOT. lexist ) THEN
77  CALL abor1_sfx('ERROR WHILE OPENING '//hfile//' THIS FILE IS MISSING'// &
78  ' IN THE RUN DIRECTORY')
79  ENDIF
80 ENDIF
81 
82 kunit = 21
83 !
84 IF (hform=='FORMATTED') THEN
85  OPEN(unit=kunit,file=hfile,action=haction, &
86  form=hform, err=100 )
87 ELSE
88  IF (haccess=='DIRECT') THEN
89  OPEN(unit=kunit,file=hfile,action=haction, &
90  form=hform,access=haccess,recl=krecl, err=100 )
91  ELSE
92  OPEN(unit=kunit,file=hfile,action=haction, &
93  form=hform, err=100 )
94  END IF
95 END IF
96 !
97 IF (lhook) CALL dr_hook('OPEN_FILE_NC',1,zhook_handle)
98 RETURN
99 100 CONTINUE
100  CALL get_luout('NC ',iluout)
101 WRITE(iluout,*) 'Error when opening file ',hfile
102  CALL abor1_sfx('OPEN_FILE_NC: ERROR WHEN OPENING FILE '//hfile)
103 IF (lhook) CALL dr_hook('OPEN_FILE_NC',1,zhook_handle)
104 !-------------------------------------------------------------------------------
105 !
106 END SUBROUTINE open_file_nc
subroutine open_file_nc(KUNIT, HFILE, HFORM, HACTION, HACCESS, KRECL)
Definition: open_file_nc.F90:6
subroutine abor1_sfx(YTEXT)
Definition: abor1_sfx.F90:6
subroutine get_luout(HPROGRAM, KLUOUT)
Definition: get_luout.F90:6