New URL for NEMO forge!   http://forge.nemo-ocean.eu

Since March 2022 along with NEMO 4.2 release, the code development moved to a self-hosted GitLab.
This present forge is now archived and remained online for history.
obs_utils.F90 in branches/nemo_v3_3_beta/NEMOGCM/NEMO/OPA_SRC/OBS – NEMO

source: branches/nemo_v3_3_beta/NEMOGCM/NEMO/OPA_SRC/OBS/obs_utils.F90 @ 2287

Last change on this file since 2287 was 2287, checked in by smasson, 14 years ago

update licence of all NEMO files...

  • Property svn:keywords set to Id
File size: 7.0 KB
Line 
1MODULE obs_utils
2   !!======================================================================
3   !!                       ***  MODULE obs_utils   ***
4   !! Observation diagnostics: Utility functions
5   !!=====================================================================
6
7   !!----------------------------------------------------------------------
8   !!   grt_cir_dis     : Great circle distance
9   !!   grt_cir_dis_saa : Great circle distance (small angle)
10   !!   chkerr          : Error-message managment for NetCDF files
11   !!   chkdim          : Error-message managment for NetCDF files
12   !!   fatal_error     : Fatal error handling
13   !!   ddatetoymdhms   : Convert YYYYMMDD.hhmmss to components
14   !!----------------------------------------------------------------------
15   !! * Modules used
16   USE par_oce, ONLY : &        ! Precision variables
17      & wp, &
18      & dp, &
19      & i8 
20   USE in_out_manager           ! I/O manager
21 
22   IMPLICIT NONE
23
24   !! * Routine accessibility
25   PRIVATE
26   PUBLIC grt_cir_dis,     &  ! Great circle distance
27      &   grt_cir_dis_saa, &  ! Great circle distance (small angle)
28      &   str_c_to_for,    &  ! Remove non-printable chars from string
29      &   chkerr,          &  ! Error-message managment for NetCDF files
30      &   chkdim,          &  ! Check if dimensions are correct for a variable
31      &   fatal_error,     &  ! Fatal error handling
32      &   warning,         &  ! Warning handling
33      &   ddatetoymdhms       ! Convert YYYYMMDD.hhmmss to components
34         
35   !!----------------------------------------------------------------------
36   !! NEMO/OPA 3.3 , NEMO Consortium (2010)
37   !! $Id$
38   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt)
39   !!----------------------------------------------------------------------
40
41CONTAINS
42 
43#include "grt_cir_dis.h90"
44
45#include "grt_cir_dis_saa.h90"
46
47#include "str_c_to_for.h90"
48
49   SUBROUTINE chkerr( kstatus, cd_name, klineno )
50      !!----------------------------------------------------------------------
51      !!   
52      !!                    *** ROUTINE chkerr ***
53      !!
54      !! ** Purpose : Error-message managment for NetCDF files.
55      !!
56      !! ** Method  :
57      !!
58      !! ** Action  :
59      !!
60      !! History
61      !!      ! 02-12  (N. Daget)  hdlerr
62      !!      ! 06-04  (A. Vidard) f90/nemovar migration, change name
63      !!      ! 06-10  (A. Weaver) Cleanup
64      !!----------------------------------------------------------------------
65      !! * Modules used
66      USE netcdf             ! NetCDF library
67      USE dom_oce, ONLY : &  ! Ocean space and time domain variables
68         & nproc
69
70      !! * Arguments
71      INTEGER :: kstatus
72      INTEGER :: klineno
73      CHARACTER(LEN=*) :: cd_name
74     
75      !! * Local declarations
76      CHARACTER(len=200) :: clineno
77
78      ! Main computation
79      IF ( kstatus /= nf90_noerr ) THEN
80         WRITE(clineno,'(A,I8)')' at line number ', klineno
81         CALL ctl_stop( ' chkerr', ' Netcdf Error in ' // TRIM( cd_name ), &
82            &           clineno, nf90_strerror( kstatus ) )
83      ENDIF
84
85   END SUBROUTINE chkerr
86
87   SUBROUTINE chkdim( kfileid, kvarid, kndim, kdim, cd_name, klineno )
88      !!----------------------------------------------------------------------
89      !!   
90      !!                    *** ROUTINE chkerr ***
91      !!
92      !! ** Purpose : Error-message managment for NetCDF files.
93      !!
94      !! ** Method  :
95      !!
96      !! ** Action  :
97      !!
98      !! History
99      !!      ! 07-03  (K. Mogenen + E. Remy) Initial version
100      !!----------------------------------------------------------------------
101      !! * Modules used
102      USE netcdf             ! NetCDF library
103      USE dom_oce, ONLY : &  ! Ocean space and time domain variables
104         & nproc
105
106      !! * Arguments
107      INTEGER :: kfileid       ! NetCDF file id   
108      INTEGER :: kvarid        ! NetCDF variable id   
109      INTEGER :: kndim         ! Expected number of dimensions
110      INTEGER, DIMENSION(kndim) :: kdim      ! Expected dimensions
111      CHARACTER(LEN=*) :: cd_name            ! Calling routine name
112      INTEGER ::  klineno      ! Calling line number
113
114      !! * Local declarations
115      INTEGER :: indim
116      INTEGER, ALLOCATABLE, DIMENSION(:) :: &
117         & idim,ilendim
118      INTEGER :: ji
119      LOGICAL :: llerr
120      CHARACTER(len=200) :: clineno
121
122      CALL chkerr( nf90_inquire_variable( kfileid, kvarid, ndims=indim ), &
123         &         cd_name, klineno )
124
125      ALLOCATE(idim(indim),ilendim(indim))
126
127      CALL chkerr( nf90_inquire_variable( kfileid, kvarid, dimids=idim ), &
128         &         cd_name, klineno )
129
130      DO ji = 1, indim
131         CALL chkerr( nf90_inquire_dimension( kfileid, idim(ji), &
132            &                                 len=ilendim(ji) ), &
133            &         cd_name, klineno )
134      END DO
135     
136      IF ( indim /= kndim ) THEN
137         WRITE(clineno,'(A,I8)')' at line number ', klineno
138         CALL ctl_stop( ' chkdim',  &
139            &           ' Netcdf no dim error in ' // TRIM( cd_name ), &
140            &           clineno )
141      ENDIF
142
143      DO ji = 1, indim
144         IF ( ilendim(ji) /= kdim(ji) ) THEN
145            WRITE(clineno,'(A,I8)')' at line number ', klineno
146            CALL ctl_stop( ' chkdim',  &
147               &           ' Netcdf dim len error in ' // TRIM( cd_name ), &
148               &           clineno )
149         ENDIF
150      END DO
151         
152      DEALLOCATE(idim,ilendim)
153
154   END SUBROUTINE chkdim
155   
156  SUBROUTINE fatal_error( cd_name, klineno )
157      !!----------------------------------------------------------------------
158      !!
159      !!                    *** ROUTINE fatal_error ***
160      !!
161      !! ** Purpose : Fatal error handling
162      !!
163      !! ** Method  :
164      !!
165      !! ** Action  :
166      !!
167      !! History
168      !!----------------------------------------------------------------------
169      !! * Modules used
170
171      !! * Arguments
172      INTEGER :: klineno
173      CHARACTER(LEN=*) :: cd_name
174      !! * Local declarations
175      CHARACTER(len=200) :: clineno
176
177      WRITE(clineno,'(A,I8)')' at line number ', klineno
178      CALL ctl_stop( ' fatal_error', ' Error in ' // TRIM( cd_name ), &
179         &           clineno)
180     
181   END SUBROUTINE fatal_error
182
183   SUBROUTINE warning( cd_name, klineno )
184      !!----------------------------------------------------------------------
185      !!
186      !!                    *** ROUTINE warning ***
187      !!
188      !! ** Purpose : Warning handling
189      !!
190      !! ** Method  :
191      !!
192      !! ** Action  :
193      !!
194      !! History
195      !!----------------------------------------------------------------------
196      !! * Modules used
197
198      !! * Arguments
199      INTEGER :: klineno
200      CHARACTER(LEN=*) :: cd_name
201      !! * Local declarations
202      CHARACTER(len=200) :: clineno
203
204      WRITE(clineno,'(A,I8)')' at line number ', klineno
205      CALL ctl_warn( ' warning', ' Potential problem in ' // TRIM( cd_name ), &
206         &           clineno)
207     
208   END SUBROUTINE warning
209
210#include "ddatetoymdhms.h90"
211
212END MODULE obs_utils
Note: See TracBrowser for help on using the repository browser.