SURFEX v8.1
General documentation of Surfex
open_filein_ol.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_filein_ol
7 ! #######################################################
8 !!**** *OPEN_FILEIN_OL* -
9 
10 USE modd_surfex_mpi, ONLY : nrank, npio
11 !
14 !
15 USE yomhook ,ONLY : lhook, dr_hook
16 USE parkind1 ,ONLY : jprb
17 !
18 USE netcdf
19 !
20 IMPLICIT NONE
21 
22 INTEGER, DIMENSION(:), ALLOCATABLE :: ITEMP
23 LOGICAL :: LLEXIST
24 INTEGER :: JFILE,IFILE_ID
25 INTEGER :: JRET, INB
26 REAL(KIND=JPRB) :: ZHOOK_HANDLE
27 
28 !******************************************
29 
30 IF (lhook) CALL dr_hook('OPEN_FILEIN_OL',0,zhook_handle)
31 IF (nrank==npio) THEN
32  !
33  inb=0
34  ALLOCATE(itemp(SIZE(xnetcdf_filename_in)))
35  !
36  DO jfile=1,SIZE(xnetcdf_filename_in)
37  INQUIRE(file=xnetcdf_filename_in(jfile),exist=llexist)
38  IF (llexist) THEN
39  jret=nf90_open(xnetcdf_filename_in(jfile),nf90_nowrite,ifile_id)
40  IF (jret.EQ.nf90_noerr) THEN
41  inb=inb+1
42  itemp(inb)=ifile_id
43  ENDIF
44  ENDIF
45  ENDDO
46  !
47  ALLOCATE(xid_in(inb))
48  xid_in=itemp(1:inb)
49  !
50  ALLOCATE(xvar_to_filein(0))
51  ALLOCATE(xid_varin(0))
52  !
53 ENDIF
54 IF (lhook) CALL dr_hook('OPEN_FILEIN_OL',1,zhook_handle)
55 
56 !******************************************
57 
58 END SUBROUTINE open_filein_ol
integer *4, dimension(:), allocatable xid_in
character(len=200), dimension(19) xnetcdf_filename_in
integer, parameter jprb
Definition: parkind1.F90:32
integer *4, dimension(:), allocatable xid_varin
logical lhook
Definition: yomhook.F90:15
character(len=20), dimension(:), allocatable xvar_to_filein
subroutine open_filein_ol