gtdata_internal_vartable.f90
Go to the documentation of this file.
1 !
2 != gtool 変数表
3 !
4 ! Authors:: Eizi TOYODA, Yasuhiro MORIKAWA
5 ! Version:: $Id: gtdata_internal_vartable.f90,v 1.2 2009-05-29 15:03:49 morikawa Exp $
6 ! Tag Name:: $Name: $
7 ! Copyright:: Copyright (C) GFD Dennou Club, 2000-2005. All rights reserved.
8 ! License:: See COPYRIGHT[link:../../COPYRIGHT]
9 !
10 
12  !
13  ! このモジュールは gtool モジュールから直接には引用されないため、
14  ! 相当むちゃな名前の使い方をしている。ユーザは呼んではならない。
15  !
16  !=== gtool 変数表
17  !
18  ! gtool 変数というのは実は単なるハンドルと多次元イテレータであり、
19  ! ハンドルは小さな整数値である。
20  ! 実体にアクセスするためには、ハンドル値をキーにしてまずマップ表を引き、
21  ! そこで得られた vid をキーにして変数表を引いて、
22  ! 種別と種別ごとの変数番号を得る。これらはたかだかポインタ+オフセット
23  ! 参照程度のコストである。
24  ! gtool 変数は実体変数からイテレータが必要なだけ作成されるが、
25  ! この変数表は実体変数につき1エントリしか作成しないので、参照数を持つ。
26  ! このため、実体変数は変数に付いて参照数管理をしなくてもよくなる。
27 
29  use dc_types, only: string
30  implicit none
31  private
32 
33  integer, parameter, public :: vid_invalid = -1
34 
35  integer, parameter, public :: vtb_class_unused = 0
36  integer, parameter, public :: vtb_class_netcdf = 1
37  integer, parameter, public :: classes_max = 2
38 
39  type var_table_entry
40  integer:: class
41  integer:: cid
42  integer:: refcount
43  end type var_table_entry
44 
45  type(var_table_entry), save, allocatable:: table(:)
46  integer, parameter:: table_ini_size = 16
47 
48  type(gd_nc_variable_search), public, save:: gdnc_search
49 
51  public:: vartable_dump
52  public:: dimrange, ndims, query_growable
53  private:: var_table_entry, table, table_ini_size
54  private:: entry_cleanup
55 
56  interface dimrange
57  module procedure dimrange_direct
58  end interface
59 
60 contains
61 
62  subroutine vartable_dump(vid)
63  use dc_trace, only: dbgmessage
66  integer, intent(in):: vid
67  character(10):: class
68  if (.not. allocated(table)) return
69  if (vid <= 0 .or. vid > size(table)) return
70  select case(table(vid)%class)
71  case(vtb_class_netcdf)
72  class = 'netcdf'
73  case default
74  write(class, fmt="(i10)") table(vid)%class
75  end select
76  call dbgmessage('[vartable %d: class=%c cid=%d ref=%d]', &
77  & i=(/vid, table(vid)%cid, table(vid)%refcount/), &
78  & c1=trim(class))
79  select case(table(vid)%class)
80  case(vtb_class_netcdf)
81  call dbgmessage('[%c]', c1=trim(tostring(gd_nc_variable(table(vid)%cid))))
82  end select
83  end subroutine vartable_dump
84 
85  subroutine entry_cleanup(vtb_entry)
86  type(var_table_entry), intent(out):: vtb_entry(:)
87  vtb_entry(:)%class = vtb_class_unused
88  vtb_entry(:)%cid = -1
89  vtb_entry(:)%refcount = 0
90  end subroutine entry_cleanup
91 
92  subroutine vartableadd(vid, class, cid)
93  use dc_trace, only: dbgmessage
94  integer, intent(out):: vid
95  integer, intent(in):: class, cid
96  type(var_table_entry), allocatable:: tmp_table(:)
97  integer:: n
98  continue
99  ! 必要ならば初期幅確保
100  if (.not. allocated(table)) then
101  allocate(table(table_ini_size))
102  call entry_cleanup(table(:))
103  endif
104  ! 該当があれば参照数増加
105  do, n = 1, size(table)
106  if (table(n)%class == class .and. table(n)%cid == cid) then
107  table(n)%refcount = table(n)%refcount + 1
108  call dbgmessage('gtdata_vartable.add(class=%d cid=%d) found (ref=%d)', &
109  & i=(/table(n)%class, table(n)%cid, table(n)%refcount/))
110  vid = n
111  return
112  endif
113  enddo
114  ! もし空きが無ければ表を拡張
115  if (all(table(:)%class /= vtb_class_unused)) then
116  n = size(table)
117  allocate(tmp_table(n))
118  tmp_table(:) = table(:)
119  deallocate(table)
120  allocate(table(n * 2))
121  table(1:n) = tmp_table(1:n)
122  deallocate(tmp_table)
123  table(n+1:n*2) = var_table_entry(vtb_class_unused, -1, 0)
124  endif
125  do, n = 1, size(table)
126  if (table(n)%class == vtb_class_unused) then
127  table(n)%class = class
128  table(n)%cid = cid
129  table(n)%refcount = 1
130  vid = n
131  return
132  endif
133  enddo
134  vid = vid_invalid
135  end subroutine vartableadd
136 
137  subroutine vartabledelete(vid, action, err)
138  integer, intent(in):: vid
139  logical, intent(out):: action
140  logical, intent(out), optional:: err
141  if (.not. allocated(table)) goto 999
142  if (vid <= 0 .or. vid > size(table)) goto 999
143  if (table(vid)%class <= vtb_class_unused) goto 999
144  if (table(vid)%class > classes_max) goto 999
145  table(vid)%refcount = max(table(vid)%refcount - 1, 0)
146  action = (table(vid)%refcount == 0)
147  if (present(err)) err = .false.
148  return
149 999 continue
150  action = .false.
151  if (present(err)) err = .true.
152  end subroutine vartabledelete
153 
154  subroutine vartablelookup(vid, class, cid)
155  ! 同じファイル番号の変数表の中身を返す
156  integer, intent(in):: vid
157  integer, intent(out), optional:: class, cid
158  if (.not. allocated(table)) goto 999
159  if (vid <= 0 .or. vid > size(table)) goto 999
160  if (table(vid)%class <= vtb_class_unused) goto 999
161  if (table(vid)%class > classes_max) goto 999
162  if (present(class)) class = table(vid)%class
163  if (present(cid)) cid = table(vid)%cid
164  return
165 999 continue
166  if (present(class)) class = vtb_class_unused
167  end subroutine vartablelookup
168 
169  subroutine vartablemore(vid, err)
170  ! 同じファイル番号の参照カウントを増加する。
171  integer, intent(in):: vid
172  logical, intent(out), optional:: err
173  if (.not. allocated(table)) goto 999
174  if (vid <= 0 .or. vid > size(table)) goto 999
175  if (table(vid)%class <= vtb_class_unused) goto 999
176  if (table(vid)%class > classes_max) goto 999
177  table(vid)%refcount = table(vid)%refcount + 1
178  if (present(err)) err = .false.
179  return
180 999 continue
181  if (present(err)) err = .true.
182  end subroutine vartablemore
183 
184  subroutine dimrange_direct(vid, dimlo, dimhi)
186  use gtdata_netcdf_generic, only: gdncinquire => inquire
187  use dc_error, only: storeerror, nf90_einval, gt_efake
188  integer, intent(in):: vid
189  integer, intent(out):: dimlo, dimhi
190  integer:: class, cid
191  call vartablelookup(vid, class, cid)
192  select case(class)
193  case(vtb_class_netcdf)
194  dimlo = 1
195  call gdncinquire(gd_nc_variable(cid), dimlen=dimhi)
196  case default
197  call storeerror(nf90_einval, 'gtdata::dimrange')
198  end select
199  end subroutine dimrange_direct
200 
201  integer function ndims(vid) result(result)
203  use gtdata_netcdf_generic, only: gdncinquire => inquire
204  use dc_error, only: storeerror, nf90_einval
205  integer, intent(in):: vid
206  integer:: class, cid
207  call vartablelookup(vid, class, cid)
208  select case(class)
209  case(vtb_class_netcdf)
210  call gdncinquire(gd_nc_variable(cid), ndims=result)
211  case default
212  call storeerror(nf90_einval, 'gtdata::ndims')
213  end select
214  end function ndims
215 
216  subroutine query_growable(vid, result)
218  use gtdata_netcdf_generic, only: inquire
219  use dc_error, only: storeerror, nf90_einval
220  integer, intent(in):: vid
221  logical, intent(out):: result
222  integer:: class, cid
223  call vartablelookup(vid, class, cid)
224  select case(class)
225  case(vtb_class_netcdf)
226  call inquire(gd_nc_variable(cid), growable=result)
227  case default
228  call storeerror(nf90_einval, 'gtdata::ndims')
229  end select
230  end subroutine query_growable
231 
232 end module gtdata_internal_vartable
subroutine, public vartabledelete(vid, action, err)
integer, parameter, public classes_max
subroutine, public vartable_dump(vid)
type(gd_nc_variable_search), save, public gdnc_search
integer, parameter, public vtb_class_netcdf
integer, parameter, public vid_invalid
integer, parameter, public gt_efake
Definition: dc_error.f90:523
subroutine, public storeerror(number, where, err, cause_c, cause_i)
Definition: dc_error.f90:830
integer function, public ndims(vid)
subroutine, public vartablemore(vid, err)
integer, parameter, public vtb_class_unused
subroutine, public vartablelookup(vid, class, cid)
Provides kind type parameter values.
Definition: dc_types.f90:49
subroutine, public vartableadd(vid, class, cid)
subroutine, public query_growable(vid, result)
integer, parameter, public string
Character length for string.
Definition: dc_types.f90:118