11     & varname, dims, longname, units, &
    12     & xtype, time_average, average, history, err )
    55     use netcdf
, only: nf90_ebaddim
    62     use dc_date, only: dcdifftimecreate
    68     character(len = *), 
intent(in):: varname
    73     character(len = *), 
intent(in):: dims(:)
    88     character(len = *), 
intent(in):: longname
    93     character(len = *), 
intent(in):: units
    98     character(len = *), 
intent(in), 
optional:: xtype
   109     logical, 
intent(in), 
optional:: time_average
   118     logical, 
intent(in), 
optional:: average
   121     type(
gt_history), 
intent(inout), 
optional, 
target:: history
   129     logical, 
intent(out), 
optional:: err
   144     type(
gt_variable), 
pointer:: vwork(:) =>null(), dimvars(:) =>null()
   145     character(STRING):: fullname, url, cause_c
   146     integer, 
pointer:: count_work(:) =>null()
   147     integer, 
pointer:: var_avr_count_work(:) =>null()
   148     integer:: var_avr_length
   150     logical, 
pointer:: var_avr_firstput_work(:) =>null()
   151     real(DP), 
pointer:: var_avr_coefsum_work(:) =>null()
   152     real(DP), 
pointer:: var_avr_baseint_work(:) =>null()
   153     real(DP), 
pointer:: var_avr_prevtime_work(:) =>null()
   156     character(STRING):: time_name, time_xtype, time_url
   157     type(
gt_variable), 
pointer:: dimvars_work(:) =>null()
   158     logical, 
pointer:: dim_value_written_work(:) =>null()
   159     integer:: dimvars_size
   160     logical:: nv_exist, bnds_exist
   161     character(STRING):: nv_name_check, bnds_name_check
   162     character(*), 
parameter:: nv_suffix = 
'_nv'   163     character(*), 
parameter:: bnds_suffix = 
'_bnds'   165     integer, 
pointer:: dimord(:) =>null()
   166     integer:: nvars, numdims, i, stat
   167     character(*), 
parameter:: subname = 
"HistoryAddVariable1"   169     call beginsub(subname, 
'name=<%a>, dims=<%a>, longname=<%a>, units=<%a>', &
   175     if (
present(history)) 
then   183     if ( .not. hst % initialized ) 
then   185       cause_c = 
'GT_HISTORY'   190     if (
associated(hst % vars)) 
then   191       nvars = 
size(hst % vars(:))
   193       count_work => hst % count
   194       nullify(hst % vars, hst % count)
   195       allocate(hst % vars(nvars + 1), hst % count(nvars + 1))
   196       hst % vars(1:nvars) = vwork(1:nvars)
   197       hst % count(1:nvars) = count_work(1:nvars)
   198       deallocate(vwork, count_work)
   199       count_work => hst % growable_indices
   200       nullify(hst % growable_indices)
   201       allocate(hst % growable_indices(nvars + 1))
   202       hst % growable_indices(1:nvars) = count_work(1:nvars)
   203       deallocate(count_work)
   207       var_avr_count_work => hst % var_avr_count
   208       nullify( hst % var_avr_count )
   209       allocate( hst % var_avr_count(nvars + 1) )
   210       hst % var_avr_count(1:nvars) = var_avr_count_work(1:nvars)
   211       deallocate( var_avr_count_work )
   212       var_avr_data_work => hst % var_avr_data
   213       nullify(hst % var_avr_data)
   214       allocate(hst % var_avr_data(nvars + 1))
   216         hst % var_avr_data(i) % length = var_avr_data_work(i) % length
   217         allocate(hst % var_avr_data(i) % &
   218           & a_dataavr(var_avr_data_work(i) % length))
   219         hst % var_avr_data(i) % a_DataAvr = var_avr_data_work(i) % a_DataAvr
   220         deallocate( var_avr_data_work(i) % a_DataAvr )
   222       deallocate( var_avr_data_work )
   223       var_avr_firstput_work => hst % var_avr_firstput
   224       nullify( hst % var_avr_firstput )
   225       allocate( hst % var_avr_firstput(nvars + 1) )
   226       hst % var_avr_firstput(1:nvars) = var_avr_firstput_work(1:nvars)
   227       deallocate( var_avr_firstput_work )
   228       var_avr_coefsum_work => hst % var_avr_coefsum
   229       nullify( hst % var_avr_coefsum )
   230       allocate( hst % var_avr_coefsum(nvars + 1) )
   231       hst % var_avr_coefsum(1:nvars) = var_avr_coefsum_work(1:nvars)
   232       deallocate( var_avr_coefsum_work )
   233       var_avr_baseint_work => hst % var_avr_baseint
   234       nullify( hst % var_avr_baseint )
   235       allocate( hst % var_avr_baseint(nvars + 1) )
   236       hst % var_avr_baseint(1:nvars) = var_avr_baseint_work(1:nvars)
   237       deallocate( var_avr_baseint_work )
   238       var_avr_prevtime_work => hst % var_avr_prevtime
   239       nullify( hst % var_avr_prevtime )
   240       allocate( hst % var_avr_prevtime(nvars + 1) )
   241       hst % var_avr_prevtime(1:nvars) = var_avr_prevtime_work(1:nvars)
   242       deallocate( var_avr_prevtime_work )
   247       allocate(hst % vars(1), hst % count(2), hst % growable_indices(1))
   249       allocate(hst % var_avr_count(1), hst % var_avr_data(1))
   250       allocate(hst % var_avr_firstput(1), hst % var_avr_coefsum(1))
   251       allocate(hst % var_avr_baseint(1), hst % var_avr_prevtime(1))
   253     nvars = 
size(hst % vars(:))
   254     hst % growable_indices(nvars) = 0
   255     if ( nvars < 2 ) 
then   256       hst % count(nvars) = 0
   258       hst % count(nvars) = hst % count(1)
   262     if (
size(dims) == 1 .and. trim(dims(1)) == 
'') 
then   267     allocate( dimvars(numdims) )
   268     allocate( dimord(numdims) )
   277       if (dimord(i) == 0) 
then   279         cause_c = 
cprintf(
'"%c" dimension is not found.', c1=trim(dims(i)))
   289       if (dimord(i) == hst % unlimited_index) 
then   290         hst % growable_indices(nvars) = i
   295     call inquire(hst % dimvars(1), url=url)
   297     call create(hst % vars(nvars), trim(fullname), dimvars, xtype=xtype)
   298     if ( 
associated(dimvars) ) 
deallocate( dimvars )
   301     if (hst % growable_indices(nvars) /= 0) 
then   302       call slice(hst % vars(nvars), hst % growable_indices(nvars), &
   303         & start=1, count=1, stride=1)
   305     call put_attr(hst % vars(nvars), 
'long_name', longname)
   306     call put_attr(hst % vars(nvars), 
'units', units)
   311       hst % var_avr_count(nvars) = 0
   315       timevar => hst % dimvars( hst % unlimited_index )
   318         & name = time_name, url = time_url, & 
   319         & xtype = time_xtype )                
   322       call inquire(hst % vars(nvars), 
size = var_avr_length )
   325       hst % var_avr_data(nvars) % length = var_avr_length
   326       allocate(hst % var_avr_data(nvars) % a_DataAvr(var_avr_length))
   327       hst % var_avr_data(nvars) % a_DataAvr = 0.0_dp
   330       hst % var_avr_firstput = .true.
   331       hst % var_avr_coefsum(nvars) = 0.0_dp
   332       hst % var_avr_baseint(nvars) = 0.0_dp
   336       hst % var_avr_prevtime(nvars) = hst % var_avr_baseint(nvars)
   339       if ( hst % growable_indices(nvars) < 1 ) 
then   341         cause_c = trim(varname)
   348         & 
value = trim(time_name) // bnds_suffix ) 
   351       call put_attr( var = hst % vars(nvars), & 
   352         & name = 
'cell_methods', &              
   353         & 
value = trim(time_name) // 
': mean' ) 
   356       dimvars_size = 
size( hst % dimvars )
   358       do i = 1, dimvars_size
   360           & var = hst % dimvars(i), & 
   361           & name = nv_name_check )    
   362         if ( trim(time_name) // trim(nv_suffix) == trim(nv_name_check) ) 
then   367       if ( .not. nv_exist ) 
then   368         dimvars_work => hst % dimvars
   369         dim_value_written_work => hst % dim_value_written
   370         nullify(hst % dimvars, hst % dim_value_written)
   371         allocate(hst % dimvars(dimvars_size + 1))
   372         allocate(hst % dim_value_written(dimvars_size + 1))
   373         hst % dimvars(1:dimvars_size) = dimvars_work(1:dimvars_size)
   374         hst % dim_value_written(1:dimvars_size) = dim_value_written_work(1:dimvars_size)
   375         deallocate(dimvars_work)
   376         deallocate(dim_value_written_work)
   378           & var = hst % dimvars(dimvars_size + 1), &   
   379           & url = trim(time_url) // trim(nv_suffix), & 
   380           & length = 2, xtype = 
'integer' )            
   381         hst % time_nv_index = dimvars_size + 1
   382         call put_attr( var = hst % dimvars(dimvars_size + 1), & 
   383           & name = 
'long_name', &                               
   384           & 
value = 
'number of vertices of time')               
   385         call put_attr( var = hst % dimvars(dimvars_size + 1), & 
   386           & name = 
'units', 
value = 
'1' )                       
   387         call put( var = hst % dimvars(dimvars_size + 1), & 
   389         hst % dim_value_written(dimvars_size + 1) = .true.
   396           & var = hst % vars(i), &   
   397           & name = bnds_name_check ) 
   398         if ( trim(time_name) // trim(bnds_suffix) == trim(bnds_name_check) ) 
then   403       if ( 
associated(dimord) )  
deallocate( dimord )
   404       if ( .not. bnds_exist ) 
then   407           &  varname = trim(time_name) // trim(bnds_suffix), &
   408           &     dims = 
stoa( trim(time_name) // trim(nv_suffix), &
   409           &                  trim(time_name) ), &             
   410           & longname = 
'bounds of time', &                    
   411           & units = hst % unlimited_units, &                  
   412           & xtype = time_xtype )                              
   417       hst % var_avr_count(nvars) = -1
   421       hst % var_avr_data(nvars) % length = var_avr_length
   422       allocate(hst % var_avr_data(nvars) % a_DataAvr(var_avr_length))
   423       hst % var_avr_data(nvars) % a_DataAvr = 0.0_dp
   426       hst % var_avr_firstput = .true.
   427       hst % var_avr_coefsum(nvars) = 0.0_dp
   428       hst % var_avr_baseint(nvars) = 0.0_dp
   432       hst % var_avr_prevtime(nvars) = hst % var_avr_baseint(nvars)
   438     if ( 
associated(dimvars) ) 
deallocate( dimvars )
   439     if ( 
associated(dimord) )  
deallocate( dimord )
   444     & varinfo, history, err )
   472     type(
gt_history),         
intent(inout), 
optional:: history
   480     logical, 
intent(out), 
optional:: err
   494     character(len = *), 
parameter:: subname = 
"HistoryAddVariable2"   496     call beginsub(subname, 
'varname=<%c>, dims=<%c>, longname=<%c>', &
   497       & c1=trim(varinfo % name), c2=trim(
joinchar(varinfo % dims)),   &
   498       & c3=trim(varinfo % longname)                               )
   500       & history = history, &              
   501       & varname = varinfo % name, &       
   502       & dims = varinfo % dims, &          
   503       & longname = varinfo % longname, &  
   504       & units = varinfo % units, &        
   505       & xtype = varinfo % xtype, &        
   506       & time_average = varinfo % time_average, & 
   508     if (
associated( varinfo % attrs )) 
then   509       call append_attrs( varinfo % name, varinfo % attrs, history )
 
type(gt_history), target, save, public default
 
integer, parameter, public dc_enotinit
 
integer, parameter, public hst_enodependtime
 
integer, parameter, public token
単語やキーワードを保持する文字型変数の種別型パラメタ 
 
logical function, public present_and_true(arg)
 
character, parameter, public gt_atmark
 
integer, parameter, public hst_empinoaxisdata
 
recursive subroutine historyaddvariable1(varname, dims, longname, units, xtype, time_average, average, history, err)
 
subroutine, public storeerror(number, where, err, cause_c, cause_i)
 
integer, parameter, public dc_noerr
 
character(string) function, public joinchar(carray, expr)
 
integer, parameter, public dp
倍精度実数型変数 
 
subroutine, public dbgmessage(fmt, i, r, d, L, n, c1, c2, c3, ca)
 
subroutine, public beginsub(name, fmt, i, r, d, L, n, c1, c2, c3, ca, version)
 
subroutine historyaddvariable2(varinfo, history, err)
 
subroutine, public endsub(name, fmt, i, r, d, L, n, c1, c2, c3, ca)
 
integer, parameter, public string
文字列を保持する 文字型変数の種別型パラメタ