SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
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 !
12 USE modd_ol_fileid, ONLY : xnetcdf_filename_in, xid_in, &
13  xvar_to_filein, xid_varin
14 !
15 USE yomhook ,ONLY : lhook, dr_hook
16 USE parkind1 ,ONLY : jprb
17 !
18 IMPLICIT NONE
19 include "netcdf.inc"
20 
21 INTEGER, DIMENSION(:), ALLOCATABLE :: itemp
22 LOGICAL :: llexist
23 INTEGER :: jfile,ifile_id
24 INTEGER :: jret, inb
25 REAL(KIND=JPRB) :: zhook_handle
26 
27 !******************************************
28 
29 IF (lhook) CALL dr_hook('OPEN_FILEIN_OL',0,zhook_handle)
30 IF (nrank==npio) THEN
31  !
32 !$OMP SINGLE
33  !
34  inb=0
35  ALLOCATE(itemp(SIZE(xnetcdf_filename_in)))
36  !
37  DO jfile=1,SIZE(xnetcdf_filename_in)
38  INQUIRE(file=xnetcdf_filename_in(jfile),exist=llexist)
39  IF (llexist) THEN
40  jret=nf_open(xnetcdf_filename_in(jfile),nf_nowrite,ifile_id)
41  IF (jret.EQ.nf_noerr) THEN
42  inb=inb+1
43  itemp(inb)=ifile_id
44  ENDIF
45  ENDIF
46  ENDDO
47  !
48  ALLOCATE(xid_in(inb))
49  xid_in=itemp(1:inb)
50  !
51  ALLOCATE(xvar_to_filein(0))
52  ALLOCATE(xid_varin(0))
53  !
54 !$OMP END SINGLE
55  !
56 ENDIF
57 IF (lhook) CALL dr_hook('OPEN_FILEIN_OL',1,zhook_handle)
58 
59 !******************************************
60 
61 END SUBROUTINE open_filein_ol
subroutine open_filein_ol