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_memory = 1
37  integer, parameter, public :: vtb_class_netcdf = 2
38  integer, parameter, public :: classes_max = 2
39 
41  integer:: class
42  integer:: cid
43  integer:: refcount
44  end type var_table_entry
45 
46  type(var_table_entry), save, allocatable:: table(:)
47  integer, parameter:: table_ini_size = 16
48 
49  type(gd_nc_variable_search), public, save:: gdnc_search
50 
52  public:: vartable_dump
53  public:: dimrange, ndims, query_growable
55  private:: entry_cleanup
56 
57  interface dimrange
58  module procedure dimrange_direct
59  end interface
60 
61 contains
62 
63  subroutine vartable_dump(vid)
64  use dc_trace, only: dbgmessage
67  integer, intent(in):: vid
68  character(10):: class
69  if (.not. allocated(table)) return
70  if (vid <= 0 .or. vid > size(table)) return
71  select case(table(vid)%class)
72  case(vtb_class_netcdf)
73  class = 'netcdf'
74  case(vtb_class_memory)
75  class = 'memory'
76  case default
77  write(class, fmt="(i10)") table(vid)%class
78  end select
79  call dbgmessage('[vartable %d: class=%c cid=%d ref=%d]', &
80  & i=(/vid, table(vid)%cid, table(vid)%refcount/), &
81  & c1=trim(class))
82  select case(table(vid)%class)
83  case(vtb_class_netcdf)
84  call dbgmessage('[%c]', c1=trim(tostring(gd_nc_variable(table(vid)%cid))))
85  end select
86  end subroutine vartable_dump
87 
88  subroutine entry_cleanup(vtb_entry)
89  type(var_table_entry), intent(out):: vtb_entry(:)
90  vtb_entry(:)%class = vtb_class_unused
91  vtb_entry(:)%cid = -1
92  vtb_entry(:)%refcount = 0
93  end subroutine entry_cleanup
94 
95  subroutine vartableadd(vid, class, cid)
96  use dc_trace, only: dbgmessage
97  integer, intent(out):: vid
98  integer, intent(in):: class, cid
99  type(var_table_entry), allocatable:: tmp_table(:)
100  integer:: n
101  continue
102  ! 必要ならば初期幅確保
103  if (.not. allocated(table)) then
104  allocate(table(table_ini_size))
105  call entry_cleanup(table(:))
106  endif
107  ! 該当があれば参照数増加
108  do, n = 1, size(table)
109  if (table(n)%class == class .and. table(n)%cid == cid) then
110  table(n)%refcount = table(n)%refcount + 1
111  call dbgmessage('gtdata_vartable.add(class=%d cid=%d) found (ref=%d)', &
112  & i=(/table(n)%class, table(n)%cid, table(n)%refcount/))
113  vid = n
114  return
115  endif
116  enddo
117  ! もし空きが無ければ表を拡張
118  if (all(table(:)%class /= vtb_class_unused)) then
119  n = size(table)
120  allocate(tmp_table(n))
121  tmp_table(:) = table(:)
122  deallocate(table)
123  allocate(table(n * 2))
124  table(1:n) = tmp_table(1:n)
125  deallocate(tmp_table)
126  table(n+1:n*2) = var_table_entry(vtb_class_unused, -1, 0)
127  endif
128  do, n = 1, size(table)
129  if (table(n)%class == vtb_class_unused) then
130  table(n)%class = class
131  table(n)%cid = cid
132  table(n)%refcount = 1
133  vid = n
134  return
135  endif
136  enddo
137  vid = vid_invalid
138  end subroutine vartableadd
139 
140  subroutine vartabledelete(vid, action, err)
141  integer, intent(in):: vid
142  logical, intent(out):: action
143  logical, intent(out), optional:: err
144  if (.not. allocated(table)) goto 999
145  if (vid <= 0 .or. vid > size(table)) goto 999
146  if (table(vid)%class <= vtb_class_unused) goto 999
147  if (table(vid)%class > classes_max) goto 999
148  table(vid)%refcount = max(table(vid)%refcount - 1, 0)
149  action = (table(vid)%refcount == 0)
150  if (present(err)) err = .false.
151  return
152 999 continue
153  action = .false.
154  if (present(err)) err = .true.
155  end subroutine vartabledelete
156 
157  subroutine vartablelookup(vid, class, cid)
158  ! 同じファイル番号の変数表の中身を返す
159  integer, intent(in):: vid
160  integer, intent(out), optional:: class, cid
161  if (.not. allocated(table)) goto 999
162  if (vid <= 0 .or. vid > size(table)) goto 999
163  if (table(vid)%class <= vtb_class_unused) goto 999
164  if (table(vid)%class > classes_max) goto 999
165  if (present(class)) class = table(vid)%class
166  if (present(cid)) cid = table(vid)%cid
167  return
168 999 continue
169  if (present(class)) class = vtb_class_unused
170  end subroutine vartablelookup
171 
172  subroutine vartablemore(vid, err)
173  ! 同じファイル番号の参照カウントを増加する。
174  integer, intent(in):: vid
175  logical, intent(out), optional:: err
176  if (.not. allocated(table)) goto 999
177  if (vid <= 0 .or. vid > size(table)) goto 999
178  if (table(vid)%class <= vtb_class_unused) goto 999
179  if (table(vid)%class > classes_max) goto 999
180  table(vid)%refcount = table(vid)%refcount + 1
181  if (present(err)) err = .false.
182  return
183 999 continue
184  if (present(err)) err = .true.
185  end subroutine vartablemore
186 
187  subroutine dimrange_direct(vid, dimlo, dimhi)
189  use gtdata_netcdf_generic, only: gdncinquire => inquire
190  use dc_error, only: storeerror, nf90_einval, gt_efake
191  integer, intent(in):: vid
192  integer, intent(out):: dimlo, dimhi
193  integer:: class, cid
194  call vartablelookup(vid, class, cid)
195  select case(class)
196  case(vtb_class_memory)
197  call storeerror(gt_efake, 'gtdata::dimrange')
198  case(vtb_class_netcdf)
199  dimlo = 1
200  call gdncinquire(gd_nc_variable(cid), dimlen=dimhi)
201  case default
202  call storeerror(nf90_einval, 'gtdata::dimrange')
203  end select
204  end subroutine dimrange_direct
205 
206  integer function ndims(vid) result(result)
208  use gtdata_netcdf_generic, only: gdncinquire => inquire
209  use dc_error, only: storeerror, nf90_einval
210  integer, intent(in):: vid
211  integer:: class, cid
212  call vartablelookup(vid, class, cid)
213  select case(class)
214  case(vtb_class_memory)
215  result = 1
216  case(vtb_class_netcdf)
217  call gdncinquire(gd_nc_variable(cid), ndims=result)
218  case default
219  call storeerror(nf90_einval, 'gtdata::ndims')
220  end select
221  end function ndims
222 
223  subroutine query_growable(vid, result)
225  use gtdata_netcdf_generic, only: inquire
226  use dc_error, only: storeerror, nf90_einval
227  integer, intent(in):: vid
228  logical, intent(out):: result
229  integer:: class, cid
230  call vartablelookup(vid, class, cid)
231  select case(class)
232  case(vtb_class_memory)
233  result = .false.
234  case(vtb_class_netcdf)
235  call inquire(gd_nc_variable(cid), growable=result)
236  case default
237  call storeerror(nf90_einval, 'gtdata::ndims')
238  end select
239  end subroutine query_growable
240 
241 end module gtdata_internal_vartable
subroutine, public vartabledelete(vid, action, err)
integer, parameter, public classes_max
integer, parameter, private table_ini_size
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
subroutine, private entry_cleanup(vtb_entry)
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 dimrange_direct(vid, dimlo, dimhi)
type(var_table_entry), dimension(:), allocatable, save, private table
subroutine, public vartablemore(vid, err)
subroutine, public dbgmessage(fmt, i, r, d, L, n, c1, c2, c3, ca)
Definition: dc_trace.f90:509
integer, parameter, public vtb_class_unused
subroutine, public vartablelookup(vid, class, cid)
種別型パラメタを提供します。
Definition: dc_types.f90:49
subroutine, public vartableadd(vid, class, cid)
integer, parameter, public vtb_class_memory
subroutine, public query_growable(vid, result)
integer, parameter, public string
文字列を保持する 文字型変数の種別型パラメタ
Definition: dc_types.f90:118