SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
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, DGU, &
7  hmask,haction)
8 ! ######################
9 !
10 !!**** *INIT_IO_SURF_NC* Keep in memory the netcdf ID of the output files
11 !!
12 !! PURPOSE
13 !! -------
14 !
15 !!
16 !!** IMPLICIT ARGUMENTS
17 !! ------------------
18 !! None
19 !!
20 !! REFERENCE
21 !! ---------
22 !!
23 !! AUTHOR
24 !! ------
25 !! F. Habets *Meteo France*
26 !!
27 !! MODIFICATIONS
28 !! -------------
29 !! modified 05/04 by P. LeMoigne *Meteo France*
30 !! modified 06/10 by S. Faroux *Meteo France*
31 !!=================================================================
32 !
33 !* 0. DECLARATIONS
34 ! ------------
35 !
38 USE modd_surf_atm_n, ONLY : surf_atm_t
39 !
40 !
41 USE modd_surfex_mpi, ONLY : nindex, npio, nrank
42 !
43 !
44 USE modd_io_surf_nc, ONLY : nmask, cfilein_nc, cfileout_nc, lmask, nid_nc, &
45  cmask, lcreated, cfileout_nc_save, ldef
46 !
48 !
50 USE modi_get_size_full_n
51 USE modi_get_type_dim_n
52 USE modi_init_io_surf_mask_n
53 !
54 USE modi_get_dim_full_n
55 !
56 USE yomhook ,ONLY : lhook, dr_hook
57 USE parkind1 ,ONLY : jprb
58 !
59 IMPLICIT NONE
60 !
61 include "netcdf.inc"
62 !
63 !
64 TYPE(data_cover_t), INTENT(INOUT) :: dtco
65 
66 TYPE(surf_atm_t), INTENT(INOUT) :: u
67 TYPE(diag_surf_atm_t), INTENT(INOUT) :: dgu
68 !
69  CHARACTER(LEN=6), INTENT(IN) :: hmask
70  CHARACTER(LEN=5), INTENT(IN) :: haction
71 !
72 INTEGER :: ifull, il, ilu, iluout, iret
73 LOGICAL :: gexist, gopened
74 !
75 REAL(KIND=JPRB) :: zhook_handle
76 !------------------------------------------------------------------------------
77 IF (lhook) CALL dr_hook('INIT_IO_SURF_NC_N',0,zhook_handle)
78 !
79 lmask = .true.
80 !
81 !$OMP BARRIER
82 !
83 IF (haction=='READ ') THEN
84  INQUIRE(file=cfilein_nc,exist=gexist)
85  IF (gexist) THEN
86  IF (nrank==npio) THEN
87 !$OMP SINGLE
88  iret = nf_open(cfilein_nc,nf_nowrite,nid_nc)
89 !$OMP END SINGLE
90  ENDIF
91  CALL read_surf(&
92  'NC ','DIM_FULL',ifull,iret,hdir='A')
93  ENDIF
94 ELSE
95  CALL get_dim_full_n(u, &
96  ifull)
97  IF (nrank==npio) THEN
98 !$OMP SINGLE
99  INQUIRE(file=cfileout_nc,exist=gexist)
100  INQUIRE(file=cfileout_nc,opened=gopened)
101  IF (.NOT.gopened) THEN
102  iret = nf_open(cfileout_nc,nf_write,nid_nc)
103  ENDIF
104  IF (ldef) iret = nf_redef(nid_nc)
105 !$OMP END SINGLE
106  ENDIF
107 ENDIF
108 !
109 ! nindex is needed for call to get_size_full_n. In init_index_mpi,
110 ! it's not initialized for first readings.
111 IF (.NOT.ALLOCATED(nindex)) THEN
112  ALLOCATE(nindex(ifull))
113  nindex(:) = 0
114 ENDIF
115 !
116 ! size by MPI task. NINDEX is supposed to be initialized at this step.
117  CALL get_size_full_n(u, &
118  'OFFLIN',ifull,ilu)
119 !
120 il = ilu
121  CALL get_type_dim_n(dtco, u, &
122  hmask,il)
123 !
124  CALL init_io_surf_mask_n(dtco, u, &
125  hmask, il, iluout, ilu, nmask)
126 !
127  cmask = hmask
128 !
129 !$OMP BARRIER
130 !------------------------------------------------------------------------------
131 IF (lhook) CALL dr_hook('INIT_IO_SURF_NC_N',1,zhook_handle)
132 !------------------------------------------------------------------------------
133 !
134 END SUBROUTINE init_io_surf_nc_n
subroutine get_type_dim_n(DTCO, U, HTYPE, KDIM)
subroutine init_io_surf_nc_n(DTCO, U, DGU, HMASK, HACTION)
subroutine get_dim_full_n(U, KDIM_FULL)
subroutine get_size_full_n(U, HPROGRAM, KDIM_FULL, KSIZE_FULL)
subroutine init_io_surf_mask_n(DTCO, U, HMASK, KSIZE, KLUOUT, KFULL, KMASK)