source: LMDZ5/branches/testing/tools/Max_diff_nc_with_lib/NetCDF95/find_coord.f90 @ 1795

Last change on this file since 1795 was 1795, checked in by Ehouarn Millour, 11 years ago

Version testing basee sur la r1794


Testing release based on r1794

File size: 3.2 KB
Line 
1module find_coord_m
2
3  implicit none
4
5contains
6
7  subroutine find_coord(ncid, name, dimid, varid, std_name)
8
9    ! This procedure returns the name, dimension id or variable id of
10    ! the NetCDF coordinate with standard name "std_name", if such a
11    ! coordinate exists. The standard name is only used to know what
12    ! to search, it is not used for the search itself. The search
13    ! itself is done via a string match on the attribute "units".
14
15    use netcdf, only: NF90_MAX_NAME, NF90_NOERR
16    use nf95_get_att_m, only: nf95_get_att
17    use nf95_inq_varid_m, only: nf95_inq_varid
18    use nf95_inquire_dimension_m, only: nf95_inquire_dimension
19    use nf95_inquire_m, only: nf95_inquire
20    use nf95_inquire_variable_m, only: nf95_inquire_variable
21
22    integer, intent(in):: ncid
23
24    character(len=*), intent(out), optional:: name ! blanks if not found
25    ! The actual character argument should normally have the length
26    ! "NF90_MAX_NAME".
27
28    integer, intent(out), optional:: dimid ! 0 if not found
29    integer, intent(out), optional:: varid ! 0 if not found
30
31    character(len=*), intent(in):: std_name
32    ! standard name : "latitude", "longitude" or "time"
33
34    ! Variables local to the procedure:
35
36    character(len=13) units
37    logical exact ! "units" must be matched exactly
38
39    integer ncerr, nDimensions, dimid_local, varid_local
40    character(len=NF90_MAX_NAME) name_local
41    integer, pointer:: dimids(:)
42    character(len=80) values
43    logical found
44
45    !----------------------------------------------
46
47    select case (std_name)
48    case("longitude")
49       units="degrees_east"
50       exact=.true.
51    case("latitude")
52       units="degrees_north"
53       exact=.true.
54    case("time")
55       units=" since"
56       exact=.false.
57    case default
58       print *, "find_coord: bad value of std_name"
59       print *, "std_name = ", std_name
60       stop 1
61    end select
62
63    call nf95_inquire(ncid, nDimensions)
64    dimid_local = 0
65    found = .false.
66
67    ! Loop on dimensions:
68    do while (.not. found .and. dimid_local < nDimensions)
69       dimid_local = dimid_local + 1
70       call nf95_inquire_dimension(ncid, dimid_local, name_local)
71       call nf95_inq_varid(ncid, name_local, varid_local, ncerr)
72       if (ncerr == NF90_NOERR) then
73          call nf95_inquire_variable(ncid, varid_local, dimids=dimids)
74          if (size(dimids) == 1) then
75             if (dimids(1) == dimid_local) then
76                ! We have found a coordinate
77                call nf95_get_att(ncid, varid_local, "units", values, ncerr)
78                if (ncerr == NF90_NOERR)then
79                   if (exact) then
80                      found = values == units
81                   else
82                      found = index(values, trim(units)) /= 0
83                   end if
84                end if
85             end if
86          end if
87          deallocate(dimids) ! pointer
88       end if
89    end do
90
91    if (found) then
92       if (present(name)) name = name_local
93       if (present(dimid)) dimid = dimid_local
94       if (present(varid)) varid = varid_local
95    else
96       if (present(name)) name = ""
97       if (present(dimid)) dimid = 0
98       if (present(varid)) varid = 0
99    end if
100
101  end subroutine find_coord
102
103end module find_coord_m
Note: See TracBrowser for help on using the repository browser.