source: branches/ORCHIDEE_3_CMIP6/ORCHIDEE/src_global/utils.f90 @ 7599

Last change on this file since 7599 was 5738, checked in by josefine.ghattas, 5 years ago

Main code for soil carbon discretization from branch MICT is introduced in the trunk. See ticket #537

  1. Guenet, J. Ghattas
File size: 1.8 KB
Line 
1! =================================================================================================================================
2! MODULE       : utils
3!
4! CONTACT      : orchidee-help _at_ listes.ipsl.fr
5!
6! LICENCE      : IPSL (2011)
7! This software is governed by the CeCILL licence see
8! ORCHIDEE/ORCHIDEE_CeCILL.LIC
9!
10!>\BRIEF        Modules containing divers gerneric functions and subroutines
11!!
12!!\n DESCRIPTION: Modules containing divers gerneric functions and subroutines. Contains subroutine:
13!!                - nccheck for handeling netcdf output message.
14!!
15!! RECENT CHANGE(S): None
16!!
17!! REFERENCE(S) : None
18!!
19!! SVN          :
20!! $HeadURL$
21!! $Date$
22!! $Revision$
23!_
24!================================================================================================================================
25
26
27MODULE utils 
28
29  USE netcdf
30  USE defprec
31  USE ioipsl_para
32
33  IMPLICIT NONE
34
35  PRIVATE
36  PUBLIC nccheck 
37
38CONTAINS
39
40!! ================================================================================================================================
41!! SUBROUTINE   : nccheck
42!!
43!>\BRIEF        Check for netcdf exit status
44!!
45!! DESCRIPTION  : Launch an orchidee error message if status variable contains a netcdf error
46!!
47!! RECENT CHANGE(S) : None
48!!
49!! REFERENCE(S) : None
50!!
51!! FLOWCHART    : None
52!! \n
53!_ ================================================================================================================================
54  SUBROUTINE nccheck(status)
55    INTEGER(i_std), INTENT (IN)         :: status
56    CHARACTER(LEN=200)                  :: mesg
57   
58    IF(status /= nf90_noerr) THEN
59     
60      WRITE(numout, *) trim(nf90_strerror(status))
61      CALL ipslerr_p(3, 'nccheck', 'Netcdf error', 'Check out_orchide_XXXX output files', 'for more information')
62    END IF 
63  END SUBROUTINE nccheck
64
65END MODULE utils 
Note: See TracBrowser for help on using the repository browser.