File: netcdf4_file.f90

package info (click to toggle)
netcdf-fortran 4.5.3%2Bds-2
  • links: PTS, VCS
  • area: main
  • in suites: bullseye
  • size: 7,456 kB
  • sloc: fortran: 25,848; f90: 20,793; sh: 4,609; ansic: 1,729; makefile: 585; pascal: 292; xml: 173
file content (154 lines) | stat: -rw-r--r-- 5,233 bytes parent folder | download | duplicates (2)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
! This is part of netCDF-4. Copyright 2006 UCAR. See COPYRIGHT file
! for details.

! This file contains the netcdf-4 file open and create functions.

! @author Ed Hartnett
! -------
function nf90_open(path, mode, ncid, chunksize, cache_size, cache_nelems, &
     cache_preemption, comm, info)
  implicit none
  character (len = *), intent(in) :: path
  integer, intent(in) :: mode
  integer, intent(out) :: ncid
  integer, optional, intent(inout) :: chunksize
  integer, optional, intent(in) :: cache_size, cache_nelems
  real, optional, intent(in) :: cache_preemption
  integer, optional, intent(in) :: comm, info
  integer :: size_in, nelems_in, preemption_in
  integer :: size_out, nelems_out, preemption_out, ret
  integer :: nf90_open

  ! If using parallel, both comm and info must be provided.
  if (present(comm) .and. .not. present(info)) then
     nf90_open = NF90_EINVAL;
     return
  end if

  ! If the user specified chuck cache parameters, use them. But user
  ! may have specified one, two, or three settings. Leave the others
  ! unchanged.
  if (present(cache_size) .or. present(cache_nelems) .or. &
       present(cache_preemption)) then
     ret = nf_get_chunk_cache(size_in, nelems_in, preemption_in)
     if (ret .ne. nf90_noerr) then
        nf90_open = ret
        return
     end if
     if (present(cache_size)) then
        size_out = cache_size
     else
        size_out = size_in
     end if
     if (present(cache_nelems)) then
        nelems_out = cache_nelems
     else
        nelems_out = nelems_in
     end if
     if (present(cache_preemption)) then
        preemption_out = int(cache_preemption * 100)
     else
        preemption_out = preemption_in
     end if
     nf90_open = nf_set_chunk_cache(size_out, nelems_out, preemption_out)
     if (nf90_open .ne. nf90_noerr) return
  end if

  ! Do the open.
  if(present(chunksize)) then
     nf90_open = nf__open(path, mode, chunksize, ncid)
  else
     if (present(comm)) then
        nf90_open = nf_open_par(path, mode, comm, info, ncid)
     else
        nf90_open = nf_open(path, mode, ncid)
     end if
  end if
  if (nf90_open .ne. nf90_noerr) return

  ! If settings were changed, reset chunk chache to original settings.
  if (present(cache_size) .or. present(cache_nelems) .or. &
       present(cache_preemption)) then
     nf90_open = nf_set_chunk_cache(size_in, nelems_in, preemption_in)
  end if

end function nf90_open
! -------
function nf90_create(path, cmode, ncid, initialsize, chunksize, cache_size, &
     cache_nelems, cache_preemption, comm, info)
  implicit none
  character (len = *), intent(in) :: path
  integer, intent(in) :: cmode
  integer, intent(out) :: ncid
  integer, optional, intent(in) :: initialsize
  integer, optional, intent(inout) :: chunksize
  integer, optional, intent(in) :: cache_size, cache_nelems
  integer, optional, intent(in) :: cache_preemption
  integer, optional, intent(in) :: comm, info
  integer :: size_in, nelems_in, preemption_in
  integer :: size_out, nelems_out, preemption_out
  integer :: nf90_create
  integer :: fileSize, chunk

  ! Just ignore options netCDF-3 options for netCDF-4 files, or
  ! netCDF-4 options, for netCDF-3 files, so that the same user code
  ! can work for both cases.

  ! If using parallel, but comm and info must be provided.
  if (present(comm) .and. .not. present(info)) then
     nf90_create = NF90_EINVAL;
     return
  end if

  ! If the user specified chuck cache parameters, use them. But user
  ! may have specified one, two, or three settings. Leave the others
  ! unchanged.
  if (present(cache_size) .or. present(cache_nelems) .or. &
       present(cache_preemption)) then
     nf90_create = nf_get_chunk_cache(size_in, nelems_in, preemption_in)
     if (nf90_create .ne. nf90_noerr) return
     if (present(cache_size)) then
        size_out = cache_size
     else
        size_out = size_in
     end if
     if (present(cache_nelems)) then
        nelems_out = cache_nelems
     else
        nelems_out = nelems_in
     end if
     if (present(cache_preemption)) then
        preemption_out = cache_preemption
     else
        preemption_out = preemption_in
     end if
     nf90_create = nf_set_chunk_cache(size_out, nelems_out, preemption_out)
     if (nf90_create .ne. nf90_noerr) return
  end if

  ! Do the file create.
  if(.not. (present(initialsize) .or. present(chunksize)) ) then
     if (present(comm)) then
        nf90_create = nf_create_par(path, cmode, comm, info, ncid)
     else
        nf90_create = nf_create(path, cmode, ncid)
     end if
  else
     ! Default values per man page
     filesize = 0; chunk = nf90_sizehint_default
     if(present(initialsize)) filesize = initialsize
     if(present(chunksize  )) chunk    = chunksize
     nf90_create = nf__create(path, cmode, filesize, chunk, ncid)
     ! Pass back the value actually used
     if(present(chunksize  )) chunksize = chunk
  end if
  if (nf90_create .ne. nf90_noerr) return

  ! If settings were changed, reset chunk chache to original settings.
  if (present(cache_size) .or. present(cache_nelems) .or. &
       present(cache_preemption)) then
     nf90_create = nf_set_chunk_cache(size_in, nelems_in, preemption_in)
  end if


end function nf90_create