28     & file, title, source, institution, &
    29     & dims, dimsizes, longnames, units, origin, interval, &
    30     & xtypes, history, origind, intervald, conventions, gt_version, overwrite, quiet, &
    31     & flag_mpi_gather, flag_mpi_split, err )
    75       & dccalcreate, dccaldatecurrent, dccaldateinquire
    77     use dc_date,  only: dcdatetimecreate, 
tochar, dcdifftimecreate, &
    78       & evalbyunit, parsetimeunits
    81     character(*), 
intent(in):: file
    84     character(*), 
intent(in):: title
    87     character(*), 
intent(in):: source
    90     character(*), 
intent(in):: institution
    93     character(*), 
intent(in):: dims(:)
   112     integer, 
intent(in):: dimsizes (:)
   140     character(*), 
intent(in):: longnames (:)
   160     character(*), 
intent(in):: units(:)
   180     real, 
intent(in), 
optional:: origin
   197     real, 
intent(in), 
optional:: interval
   222     character(*), 
intent(in),  
optional:: xtypes(:)
   252     type(
gt_history), 
intent(out), 
optional, 
target:: history
   271     real(DP), 
intent(in), 
optional:: origind
   280     real(DP), 
intent(in), 
optional:: intervald
   289     character(*), 
intent(in), 
optional:: conventions
   308     character(*), 
intent(in), 
optional:: gt_version
   330     logical, 
intent(in), 
optional:: overwrite
   344     logical, 
intent(in), 
optional:: quiet
   353     logical, 
intent(in), 
optional:: flag_mpi_gather
   370     logical, 
intent(in), 
optional:: flag_mpi_split
   392     logical, 
intent(out), 
optional:: err
   406     integer:: numdims, i, stat, blank_index
   408     character(TOKEN):: my_xtype, origin_str
   409     character(STRING):: file_work, url, x_inst, x_conv, x_gtver, nc_history
   410     character(STRING):: cause_c
   411     logical:: gtver_add, overwrite_required
   412     character(TOKEN):: username
   413     type(dc_cal):: cal_standard
   414     type(dc_cal_date):: now_date
   415     character(TOKEN):: now_date_str
   416     character(*), 
parameter:: subname = 
"HistoryCreate1"   417     character(*), 
parameter:: version = &
   419       & 
'$Id: historycreate.rb2f90,v 1.4 2009-11-03 05:22:46 morikawa Exp $'   421     call beginsub(subname, 
'file=%c ndims=%d',  &
   422       & c1=trim(file), i=(/
size(dims)/), &
   427       & 
'dims(:)=%a, dimsizes(:)=%a, longnames(:)=%a, units(:)=%a', &
   430     if (
present(history)) 
then   438     if ( hst % initialized ) 
then   440       cause_c = 
'GT_HISTORY'   447     if ( 
size(dimsizes)  /= numdims ) 
then   448       cause_c = 
'dimsizes, dims'   449     elseif ( 
size(longnames) /= numdims ) 
then   450       cause_c = 
'longnames, dims'   451     elseif ( 
size(units) /= numdims ) 
then   452       cause_c = 
'units, dims'   454     if ( trim(cause_c) /= 
"" ) 
then   461     allocate(hst % dimvars(numdims))
   462     allocate(hst % dim_value_written(numdims))
   463     hst % dim_value_written(:) = .false.
   464     hst % unlimited_index = 0
   469     if (trim(username) == 
'') username = 
'unknown'   473     call dccaldatecurrent( now_date )
   474     call dccalcreate( 
'gregorian', cal_standard )
   475     call dccaldateinquire( now_date_str, date = now_date, cal = cal_standard )
   477     nc_history = trim(now_date_str) // 
' ' // &
   478       &       trim(username) // &
   479       &       
'> gtool_history: HistoryCreate' // &
   484     hst % mpi_gather = .false.
   485     hst % mpi_split  = .false.
   495       if ( 
present(xtypes) ) 
then   496         if ( 
size(xtypes) >= i ) 
then   500       url = 
urlmerge(file=file, var=dims(i))
   501       overwrite_required = .true.
   504         & hst % dimvars(i), trim(url), &
   505         & dimsizes(i), xtype=trim(my_xtype), &
   506         & overwrite=overwrite_required)
   530       if (trim(institution) /= 
"") 
then   533         x_inst = 
"a gtool_history (by GFD Dennou Club) user"   535       call put_attr(hst % dimvars(i), 
'+Conventions', trim(x_conv))
   537         call put_attr(hst % dimvars(i), 
'+gt_version', trim(x_gtver))
   540       call put_attr(hst % dimvars(i), 
'+title', title)
   541       call put_attr(hst % dimvars(i), 
'+source', source)
   542       call put_attr(hst % dimvars(i), 
'+institution', trim(x_inst))
   543       call put_attr(hst % dimvars(i), 
'+history', trim(nc_history))
   544       call put_attr(hst % dimvars(i), 
'long_name', trim(longnames(i)))
   545       call put_attr(hst % dimvars(i), 
'units', trim(units(i)))
   546       if (dimsizes(i) == 0) 
then   547         hst % unlimited_index = i
   548         hst % unlimited_units = units(i)
   554     nullify(hst % vars, hst % growable_indices, hst % count)
   557     if ( hst % unlimited_index == 0 ) 
then   560       blank_index = index( trim( adjustl(hst % unlimited_units) ), 
' ' )
   561       if ( blank_index > 1  ) 
then   562         hst % unlimited_units = hst % unlimited_units(1:blank_index-1)
   564       hst % unlimited_units_symbol = parsetimeunits( hst % unlimited_units )
   567           & 
'units of time (%c) can not be recognized as units of time. ' // &
   568           & 
'This units is treated as (%c)', &
   569           & c1 = trim(hst % unlimited_units), c2 = 
'sec')
   575     if ( 
present(interval) ) 
then   576       hst % interval = interval
   577     elseif ( 
present(intervald) ) 
then   578       hst % interval = intervald
   582     if ( 
present (origin) ) 
then   583       hst % origin = origin
   584       hst % origin_setting = .true.
   585     elseif( 
present(origind) ) 
then   586       hst % origin = origind
   587       hst % origin_setting = .true.
   590       hst % origin_setting = .false.
   592     origin_str = trim( 
tochar( hst % origin ) ) // &
   593       &          
' [' // trim( hst % unlimited_units ) // 
']'   594     hst % newest = hst % origin
   595     hst % oldest = hst % origin
   599     hst % time_bnds = hst % origin
   600     hst % time_bnds_output_count = 0
   606         & 
'"%c" is created (origin=%c)', &
   607         & c1 = trim( file_work ), &
   608         & c2 = trim( origin_str ), rank_mpi = -1 )
   613     hst % initialized = .true.
   615     call storeerror(stat, subname, err, cause_c=cause_c)
   616     call endsub(subname, 
'stat=%d', i = (/stat/) )
   620     & file, title, source, institution, &
   621     & dims, dimsizes, longnames, units, origin, interval, &
   622     & xtypes, history, conventions, gt_version, overwrite, quiet, &
   623     & flag_mpi_gather, flag_mpi_split, err )
   665     use dc_date,  only: dcdatetimecreate, 
tochar, dcdifftimecreate, &
   666       & evalbyunit, parsetimeunits
   671     character(*), 
intent(in):: file
   674     character(*), 
intent(in):: title
   677     character(*), 
intent(in):: source
   680     character(*), 
intent(in):: institution
   683     character(*), 
intent(in):: dims(:)
   702     integer, 
intent(in):: dimsizes (:)
   730     character(*), 
intent(in):: longnames (:)
   750     character(*), 
intent(in):: units(:)
   812     character(*), 
intent(in),  
optional:: xtypes(:)
   842     type(
gt_history), 
intent(out), 
optional, 
target:: history
   861     character(*), 
intent(in), 
optional:: conventions
   880     character(*), 
intent(in), 
optional:: gt_version
   902     logical, 
intent(in), 
optional:: overwrite
   916     logical, 
intent(in), 
optional:: quiet
   925     logical, 
intent(in), 
optional:: flag_mpi_gather
   942     logical, 
intent(in), 
optional:: flag_mpi_split
   964     logical, 
intent(out), 
optional:: err
   979     real(DP):: origind, intervald
   980     integer:: i, numdims, blank_index
   981     character(TOKEN):: unlimited_units
   982     integer:: unit_symbol
   984     character(STRING):: cause_c
   985     character(*), 
parameter:: subname = 
"HistoryCreate2"   986     character(*), 
parameter:: version = &
   988       & 
'$Id: historycreate.rb2f90,v 1.4 2009-11-03 05:22:46 morikawa Exp $'   990     call beginsub(subname, 
'file=%c ndims=%d',  &
   991       & c1=trim(file), i=(/
size(dims)/), &
   996     unlimited_units = 
'sec'   998       if (dimsizes(i) == 0) unlimited_units = units(i)
  1000     blank_index = index( trim( adjustl(unlimited_units) ), 
' ' )
  1001     if ( blank_index > 1  ) 
then  1002       unlimited_units = unlimited_units(1:blank_index-1)
  1004     unit_symbol = parsetimeunits( unlimited_units )
  1006     if (
present(interval)) 
then  1007       intervald = evalbyunit( interval, 
'', unit_symbol )
  1011     origind = evalbyunit( origin, 
'', unit_symbol )
  1013       & file = file, title = title, &
  1014       & source = source, institution = institution, &
  1015       & dims = dims, dimsizes = dimsizes, &
  1016       & longnames = longnames, units = units, &
  1017       & xtypes = xtypes, history = history, &
  1018       & origind = origind, intervald = intervald, &
  1019       & conventions = conventions, gt_version = gt_version, &
  1020       & overwrite = overwrite, quiet = quiet, &
  1021       & flag_mpi_gather = flag_mpi_gather, flag_mpi_split = flag_mpi_split, &
  1023     if (
present(history)) 
then  1029     call storeerror(stat, subname, cause_c=cause_c)
  1030     call endsub(subname, 
'stat=%d', i = (/stat/) )
  1034     & axes, origin, interval, history, origind, intervald, conventions, gt_version, &
  1035     & overwrite, quiet, flag_mpi_gather, flag_mpi_split, err )
  1073     character(*), 
intent(in):: file
  1077     character(*), 
intent(in):: title, source, institution
  1087     real, 
intent(in), 
optional:: origin, interval
  1088     type(
gt_history), 
intent(out), 
optional, 
target:: history
  1089     real(DP), 
intent(in), 
optional:: origind, intervald
  1090     character(*), 
intent(in),  
optional:: conventions, gt_version
  1091     logical, 
intent(in), 
optional:: overwrite
  1092     logical, 
intent(in), 
optional:: quiet
  1101     logical, 
intent(in), 
optional:: flag_mpi_gather
  1118     logical, 
intent(in), 
optional:: flag_mpi_split
  1140     logical, 
intent(out), 
optional:: err
  1155     character(STRING), 
allocatable:: axes_name(:)
  1156     integer          , 
allocatable:: axes_length(:)
  1157     character(STRING), 
allocatable:: axes_longname(:)
  1158     character(STRING), 
allocatable:: axes_units(:)
  1159     character(STRING), 
allocatable:: axes_xtype(:)
  1161     character(len = *), 
parameter:: subname = 
"HistoryCreate3"  1163     call beginsub(subname, 
'file=%c ndims=%d', &
  1164       & c1=trim(file), i=(/
size(axes)/) )
  1170     ndims = 
size( axes(:) )
  1171     allocate( axes_name(ndims) )
  1172     allocate( axes_length(ndims) )
  1173     allocate( axes_longname(ndims) )
  1174     allocate( axes_units(ndims) )
  1175     allocate( axes_xtype(ndims) )
  1177       axes_name(i)     = axes(i) % name
  1178       axes_length(i)   = axes(i) % length
  1179       axes_longname(i) = axes(i) % longname
  1180       axes_units(i)    = axes(i) % units
  1181       axes_xtype(i)    = axes(i) % xtype
  1182       call dbgmessage(
'axes(%d):name=<%c>, length=<%d>, ' // & 
  1183         &             
'longname=<%c>, units=<%c>'     , &
  1184         &              i=(/i, axes(i) % length/)        , &
  1185         &              c1=( trim(axes(i) % name) )      , &
  1186         &              c2=( trim(axes(i) % longname) )  , &
  1187         &              c3=( trim(axes(i) % units) )    )
  1190       & dims = axes_name(:), dimsizes = axes_length(:), &
  1191       & longnames = axes_longname(:), units = axes_units(:), &
  1192       & xtypes = axes_xtype(:), &
  1193       & origin = origin, interval = interval, &
  1194       & history = history, &
  1195       & origind = origind, intervald = intervald, &
  1196       & conventions = conventions, &
  1197       & gt_version = gt_version, overwrite = overwrite, quiet = quiet, &
  1198       & flag_mpi_gather = flag_mpi_gather, &
  1199       & flag_mpi_split = flag_mpi_split, &
  1201     deallocate( axes_name )
  1202     deallocate( axes_length )
  1203     deallocate( axes_longname )
  1204     deallocate( axes_units )
  1205     deallocate( axes_xtype )
  1207       if ( .not. 
associated( axes(i) % attrs ) ) cycle
  1208       call append_attrs( axes(i) % name, axes(i) % attrs, history )
 
type(gt_history), target, save, public default
 
integer, parameter, public unit_symbol_err
 
integer, parameter, public token
単語やキーワードを保持する文字型変数の種別型パラメタ 
 
logical function, public present_and_true(arg)
 
character(string), parameter, public gtool4_netcdf_version
 
subroutine, public storeerror(number, where, err, cause_c, cause_i)
 
integer, parameter, public dc_noerr
 
logical function, public present_and_false(arg)
 
subroutine historycreate1(file, title, source, institution, dims, dimsizes, longnames, units, origin, interval, xtypes, history, origind, intervald, conventions, gt_version, overwrite, quiet, flag_mpi_gather, flag_mpi_split, err)
 
subroutine historycreate3(file, title, source, institution, axes, origin, interval, history, origind, intervald, conventions, gt_version, overwrite, quiet, flag_mpi_gather, flag_mpi_split, err)
 
character(string) function, public joinchar(carray, expr)
 
integer, parameter, public dp
倍精度実数型変数 
 
subroutine, public dbgmessage(fmt, i, r, d, L, n, c1, c2, c3, ca)
 
logical function, public present_and_not_empty(arg)
 
subroutine, public beginsub(name, fmt, i, r, d, L, n, c1, c2, c3, ca, version)
 
integer, parameter, public gt_eargsizemismatch
 
integer, parameter, public unit_symbol_sec
 
subroutine historycreate2(file, title, source, institution, dims, dimsizes, longnames, units, origin, interval, xtypes, history, conventions, gt_version, overwrite, quiet, flag_mpi_gather, flag_mpi_split, err)
 
character(string), parameter, public gtool4_netcdf_conventions
 
subroutine sysdepenvget(env, str)
 
subroutine, public endsub(name, fmt, i, r, d, L, n, c1, c2, c3, ca)
 
integer, parameter, public dc_ealreadyinit
 
integer, parameter, public string
文字列を保持する 文字型変数の種別型パラメタ