SURFEX v8.1
General documentation of Surfex
init_io_surf_ncn.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 init_io_surf_nc_n (DTCO, U, HMASK,HACTION)
7 ! ######################
8 !
9 !!**** *INIT_IO_SURF_NC* Keep in memory the netcdf ID of the output files
10 !!
11 !! PURPOSE
12 !! -------
13 !
14 !!
15 !!** IMPLICIT ARGUMENTS
16 !! ------------------
17 !! None
18 !!
19 !! REFERENCE
20 !! ---------
21 !!
22 !! AUTHOR
23 !! ------
24 !! F. Habets *Meteo France*
25 !!
26 !! MODIFICATIONS
27 !! -------------
28 !! modified 05/04 by P. LeMoigne *Meteo France*
29 !! modified 06/10 by S. Faroux *Meteo France*
30 !!=================================================================
31 !
32 !* 0. DECLARATIONS
33 ! ------------
34 !
36 USE modd_surf_atm_n, ONLY : surf_atm_t
37 !
38 !
39 USE modd_surfex_mpi, ONLY : nindex, npio, nrank
40 !
41 !
44  nfull
45 !
47 !
49 USE modi_get_size_full_n
50 USE modi_get_type_dim_n
51 USE modi_init_io_surf_mask_n
52 !
53 USE modi_get_dim_full_n
54 !
55 USE yomhook ,ONLY : lhook, dr_hook
56 USE parkind1 ,ONLY : jprb
57 !
58 USE netcdf
59 !
60 IMPLICIT NONE
61 !
62 !
63 !
64 TYPE(data_cover_t), INTENT(INOUT) :: DTCO
65 
66 TYPE(surf_atm_t), INTENT(INOUT) :: U
67 !
68  CHARACTER(LEN=6), INTENT(IN) :: HMASK
69  CHARACTER(LEN=5), INTENT(IN) :: HACTION
70 !
71 INTEGER :: IL, ILU, ILUOUT, IRET
72 LOGICAL :: GEXIST, GOPENED
73 !
74 REAL(KIND=JPRB) :: ZHOOK_HANDLE
75 !------------------------------------------------------------------------------
76 IF (lhook) CALL dr_hook('INIT_IO_SURF_NC_N',0,zhook_handle)
77 !
78 lmask = .true.
79 !
80 IF (haction=='READ ') THEN
81  INQUIRE(file=cfilein_nc,exist=gexist)
83  IF (gexist) THEN
84  iret = nf90_open(cfilein_nc,nf90_nowrite,nid_nc)
85  CALL read_surf('NC ','DIM_FULL',nfull,iret,hdir='A')
86  ENDIF
87 ELSE
88  CALL get_dim_full_n(u%NDIM_FULL, nfull)
89  IF (nrank==npio) THEN
90  INQUIRE(file=cfileout_nc,exist=gexist)
91  INQUIRE(file=cfileout_nc,opened=gopened)
92  IF (.NOT.gopened) THEN
93  iret = nf90_open(cfileout_nc,nf90_write,nid_nc)
94  ENDIF
95  IF (ldef) iret = nf90_redef(nid_nc)
96  ENDIF
98 ENDIF
99 !
100 ! nindex is needed for call to get_size_full_n. In init_index_mpi,
101 ! it's not initialized for first readings.
102 IF (.NOT.ALLOCATED(nindex).AND.nrank==npio) THEN
103  ALLOCATE(nindex(nfull))
104  nindex(:) = 0
105 ELSE
106  CALL get_dim_full_n(u%NDIM_FULL, nfull)
107 ENDIF
108 !
109 ! size by MPI task. NINDEX is supposed to be initialized at this step.
110  CALL get_size_full_n('OFFLIN',nfull,u%NSIZE_FULL,ilu)
111 !
112 il = ilu
113  CALL get_type_dim_n(dtco, u, hmask,il)
114 !
115  CALL init_io_surf_mask_n(dtco, u, hmask, il, iluout, ilu, nmask)
116 !
117 CMASK = HMASK
118 !
119 !------------------------------------------------------------------------------
120 IF (lhook) CALL dr_hook('INIT_IO_SURF_NC_N',1,zhook_handle)
121 !------------------------------------------------------------------------------
122 !
123 END SUBROUTINE init_io_surf_nc_n
subroutine get_type_dim_n(DTCO, U, HTYPE, KDIM)
character(len=28), save cfileout_nc
character(len=28), save cfileout_nc_save
subroutine get_dim_full_n(KDIM_FULL_IN, KDIM_FULL_OUT)
logical, save lmask
subroutine get_size_full_n(HPROGRAM, KDIM_FULL, KSIZE_FULL_IN, KSIZE
integer, parameter jprb
Definition: parkind1.F90:32
integer, dimension(:), pointer nmask
logical lhook
Definition: yomhook.F90:15
logical, save lcreated
integer, dimension(:), allocatable nindex
character(len=6) cmask
subroutine init_io_surf_mask_n(DTCO, U, HMASK, KSIZE, KLUOUT, KFULL, KMASK)
character(len=28), save cfile_nc
subroutine init_io_surf_nc_n(DTCO, U, HMASK, HACTION)
character(len=28), save cfilein_nc