Newer
Older
!MNH_LIC Copyright 1994-2014 CNRS, Meteo-France and Universite Paul Sabatier
!MNH_LIC This is part of the Meso-NH software governed by the CeCILL-C licence
!MNH_LIC version 1. See LICENSE, CeCILL-C_V1-en.txt and CeCILL-C_V1-fr.txt
!MNH_LIC for details. version 1.
SUBROUTINE GET_NB_PROCIO_WRITE_MNH( KNB_PROCIO, KRESP )
!
!!**** *GET_NB_PROCIO_WRITE_MNH* - gets the number of processes used for Output of file MODD_IO_SURF_MNH::COUTFILE
!!
!!
!! PURPOSE
!! -------
!! call GET_NB_PROCIO_WRITE_MNH from SURFEX to get the number of processes used
!! for Output of file MODD_IO_SURF_MNH::COUTFILE in MESO-NH (defined by user in namelist)
!!
!!** METHOD
!! ------
!!
!! EXTERNAL
!! --------
!!
!!
!! IMPLICIT ARGUMENTS
!! ------------------
!!
!! REFERENCE
!! ---------
!!
!!
!! AUTHOR
!! ------

ESCOBAR MUNOZ Juan
committed
!! M. Moge *LA - UPS* 08/01/2016
!! J. escobar 19/04/2016 : bypass , For pb IOZ/NETCDF , pretende alway 2 ( > 1 ) I/O processors for homogenus PGD files
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
!!
!! MODIFICATIONS
!! -------------
!!
!-------------------------------------------------------------------------------
!
USE MODE_FD_ll, ONLY : GETFD,JPFINL,FD_ll
USE MODD_IO_SURF_MNH, ONLY : COUT, COUTFILE
!
IMPLICIT NONE
!
!* 0. DECLARATIONS
! ------------
!
!* 0.1 Declarations of arguments
!
!CHARACTER(LEN=*), INTENT(IN) :: HFILEM ! FM-file name
INTEGER, INTENT(OUT) :: KNB_PROCIO ! number of processes used for IO
INTEGER, INTENT(OUT) :: KRESP ! return-code
!
!* 0.2 Declarations of local variables
!
!----------------------------------------------------------------
CHARACTER(LEN=JPFINL) :: YFNLFI
TYPE(FD_ll), POINTER :: TZFD
INTEGER :: IRESP
INTEGER :: ILUPRI
!
!* 1. get the number of processes used for IO
!
IRESP = 0
YFNLFI=TRIM(ADJUSTL(COUTFILE))//'.lfi'
!
TZFD=>GETFD(YFNLFI)
IF (ASSOCIATED(TZFD)) THEN

ESCOBAR MUNOZ Juan
committed
!!$ KNB_PROCIO = TZFD%nb_procio
KNB_PROCIO = 2
ELSE
IRESP = -61
END IF
!----------------------------------------------------------------
IF (IRESP.NE.0) THEN
CALL FMLOOK_ll(COUT,COUT,ILUPRI,IRESP)
WRITE (ILUPRI,*) ' exit from GET_NB_PROCIO_WRITE_MNH with RESP:',IRESP
WRITE (ILUPRI,*) ' | COUTFILE = ',COUTFILE
END IF
KRESP = IRESP
!

ESCOBAR MUNOZ Juan
committed
END SUBROUTINE GET_NB_PROCIO_WRITE_MNH