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 @ 2281

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

set proper svn properties to all files...

  • Property svn:keywords set to Id
File size: 6.7 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         
35CONTAINS
36 
37#include "grt_cir_dis.h90"
38
39#include "grt_cir_dis_saa.h90"
40
41#include "str_c_to_for.h90"
42
43   SUBROUTINE chkerr( kstatus, cd_name, klineno )
44      !!----------------------------------------------------------------------
45      !!   
46      !!                    *** ROUTINE chkerr ***
47      !!
48      !! ** Purpose : Error-message managment for NetCDF files.
49      !!
50      !! ** Method  :
51      !!
52      !! ** Action  :
53      !!
54      !! History
55      !!      ! 02-12  (N. Daget)  hdlerr
56      !!      ! 06-04  (A. Vidard) f90/nemovar migration, change name
57      !!      ! 06-10  (A. Weaver) Cleanup
58      !!----------------------------------------------------------------------
59      !! * Modules used
60      USE netcdf             ! NetCDF library
61      USE dom_oce, ONLY : &  ! Ocean space and time domain variables
62         & nproc
63
64      !! * Arguments
65      INTEGER :: kstatus
66      INTEGER :: klineno
67      CHARACTER(LEN=*) :: cd_name
68     
69      !! * Local declarations
70      CHARACTER(len=200) :: clineno
71
72      ! Main computation
73      IF ( kstatus /= nf90_noerr ) THEN
74         WRITE(clineno,'(A,I8)')' at line number ', klineno
75         CALL ctl_stop( ' chkerr', ' Netcdf Error in ' // TRIM( cd_name ), &
76            &           clineno, nf90_strerror( kstatus ) )
77      ENDIF
78
79   END SUBROUTINE chkerr
80
81   SUBROUTINE chkdim( kfileid, kvarid, kndim, kdim, cd_name, klineno )
82      !!----------------------------------------------------------------------
83      !!   
84      !!                    *** ROUTINE chkerr ***
85      !!
86      !! ** Purpose : Error-message managment for NetCDF files.
87      !!
88      !! ** Method  :
89      !!
90      !! ** Action  :
91      !!
92      !! History
93      !!      ! 07-03  (K. Mogenen + E. Remy) Initial version
94      !!----------------------------------------------------------------------
95      !! * Modules used
96      USE netcdf             ! NetCDF library
97      USE dom_oce, ONLY : &  ! Ocean space and time domain variables
98         & nproc
99
100      !! * Arguments
101      INTEGER :: kfileid       ! NetCDF file id   
102      INTEGER :: kvarid        ! NetCDF variable id   
103      INTEGER :: kndim         ! Expected number of dimensions
104      INTEGER, DIMENSION(kndim) :: kdim      ! Expected dimensions
105      CHARACTER(LEN=*) :: cd_name            ! Calling routine name
106      INTEGER ::  klineno      ! Calling line number
107
108      !! * Local declarations
109      INTEGER :: indim
110      INTEGER, ALLOCATABLE, DIMENSION(:) :: &
111         & idim,ilendim
112      INTEGER :: ji
113      LOGICAL :: llerr
114      CHARACTER(len=200) :: clineno
115
116      CALL chkerr( nf90_inquire_variable( kfileid, kvarid, ndims=indim ), &
117         &         cd_name, klineno )
118
119      ALLOCATE(idim(indim),ilendim(indim))
120
121      CALL chkerr( nf90_inquire_variable( kfileid, kvarid, dimids=idim ), &
122         &         cd_name, klineno )
123
124      DO ji = 1, indim
125         CALL chkerr( nf90_inquire_dimension( kfileid, idim(ji), &
126            &                                 len=ilendim(ji) ), &
127            &         cd_name, klineno )
128      END DO
129     
130      IF ( indim /= kndim ) THEN
131         WRITE(clineno,'(A,I8)')' at line number ', klineno
132         CALL ctl_stop( ' chkdim',  &
133            &           ' Netcdf no dim error in ' // TRIM( cd_name ), &
134            &           clineno )
135      ENDIF
136
137      DO ji = 1, indim
138         IF ( ilendim(ji) /= kdim(ji) ) THEN
139            WRITE(clineno,'(A,I8)')' at line number ', klineno
140            CALL ctl_stop( ' chkdim',  &
141               &           ' Netcdf dim len error in ' // TRIM( cd_name ), &
142               &           clineno )
143         ENDIF
144      END DO
145         
146      DEALLOCATE(idim,ilendim)
147
148   END SUBROUTINE chkdim
149   
150  SUBROUTINE fatal_error( cd_name, klineno )
151      !!----------------------------------------------------------------------
152      !!
153      !!                    *** ROUTINE fatal_error ***
154      !!
155      !! ** Purpose : Fatal error handling
156      !!
157      !! ** Method  :
158      !!
159      !! ** Action  :
160      !!
161      !! History
162      !!----------------------------------------------------------------------
163      !! * Modules used
164
165      !! * Arguments
166      INTEGER :: klineno
167      CHARACTER(LEN=*) :: cd_name
168      !! * Local declarations
169      CHARACTER(len=200) :: clineno
170
171      WRITE(clineno,'(A,I8)')' at line number ', klineno
172      CALL ctl_stop( ' fatal_error', ' Error in ' // TRIM( cd_name ), &
173         &           clineno)
174     
175   END SUBROUTINE fatal_error
176
177   SUBROUTINE warning( cd_name, klineno )
178      !!----------------------------------------------------------------------
179      !!
180      !!                    *** ROUTINE warning ***
181      !!
182      !! ** Purpose : Warning handling
183      !!
184      !! ** Method  :
185      !!
186      !! ** Action  :
187      !!
188      !! History
189      !!----------------------------------------------------------------------
190      !! * Modules used
191
192      !! * Arguments
193      INTEGER :: klineno
194      CHARACTER(LEN=*) :: cd_name
195      !! * Local declarations
196      CHARACTER(len=200) :: clineno
197
198      WRITE(clineno,'(A,I8)')' at line number ', klineno
199      CALL ctl_warn( ' warning', ' Potential problem in ' // TRIM( cd_name ), &
200         &           clineno)
201     
202   END SUBROUTINE warning
203
204#include "ddatetoymdhms.h90"
205
206END MODULE obs_utils
Note: See TracBrowser for help on using the repository browser.