Class ::xowiki::FormPage (public)

 ::xo::db::CrClass ::xowiki::FormPage[i]

Defined in

Testcases:
No testcase defined.
Source code:
namespace eval ::xowiki {}
::nsf::object::alloc ::xo::db::CrClass ::xowiki::FormPage {set :__default_metaclass ::xotcl::Class
   set :__default_superclass ::xotcl::Object
   set :abstract_p f
   set :auto_save false
   array set :db_constraints {state {{default {}} {default {}}} assignee {{references parties(party_id)} {references parties(party_id)}}}
   array set :db_slot {page_template ::xowiki::PageInstance::slot::page_template page_order ::xowiki::Page::slot::page_order creator ::xowiki::Page::slot::creator state ::xowiki::FormPage::slot::state page_id ::xowiki::Page::slot::page_id creation_date ::xo::db::Object::slot::creation_date instance_attributes ::xowiki::PageInstance::slot::instance_attributes creation_user ::xo::db::Object::slot::creation_user object_id ::xo::db::Object::slot::object_id description ::xowiki::Page::slot::description creation_ip ::xo::db::Object::slot::creation_ip text ::xowiki::Page::slot::text nls_language ::xo::db::CrItem::slot::nls_language object_title ::xo::db::Object::slot::object_title package_id ::xo::db::Object::slot::package_id security_inherit_p ::xo::db::Object::slot::security_inherit_p context_id ::xo::db::Object::slot::context_id mime_type ::xo::db::CrItem::slot::mime_type name ::xo::db::CrItem::slot::name title ::xowiki::Page::slot::title item_id ::xo::db::CrItem::slot::item_id revision_id ::xo::db::CrItem::slot::revision_id publish_date ::xowiki::Page::slot::publish_date modifying_user ::xo::db::Object::slot::modifying_user last_modified ::xo::db::Object::slot::last_modified page_instance_id ::xowiki::PageInstance::slot::page_instance_id xowiki_form_page_id ::xowiki::FormPage::slot::xowiki_form_page_id modifying_ip ::xo::db::Object::slot::modifying_ip assignee ::xowiki::FormPage::slot::assignee}
   set :folder_id -100
   set :id_column xowiki_form_page_id
   array set :long_text_slots {instance_attributes ::xowiki::PageInstance::slot::instance_attributes}
   set :mime_type text/plain
   set :name_method {}
   set :non_cached_instance_var_patterns __*
   set :object_type ::xowiki::FormPage
   set :object_type_key 0000000000001111000110010000001000000000
   set :pretty_name #xowiki.FormPage_pretty_name#
   set :pretty_plural #xowiki.FormPage_pretty_plural#
   set :security_inherit_p t
   set :sql_package_name ::xowiki::FormPage
   set :storage_type text
   set :supertype content_revision
   set :table_name xowiki_form_page
   set :with_table true}
::xowiki::FormPage proc fetch_object {-item_id:required {-revision_id 0} -object:required {-initialize:boolean true}} {
    #ns_log notice "=== fetch_object $item_id"
    #
    # We handle here just loading object instances via item_id, since
    # only live_revisions are kept in xowiki_form_instance_item_index.
    # The loading via revision_id happens as before in CrClass.
    #
    if {$item_id == 0} {
      return [next]
    }

    if {![nsf::is object $object]} {
      # if the object does not yet exist, we have to create it
      :create $object
    }

    db_with_handle db {
      set sql [::xo::dc prepare -handle $db -argtypes integer {
        select * from xowiki_form_instance_item_view where item_id = :item_id
      }]
      set selection [db_exec 0or1row $db dbqd..Formpage-fetch_object $sql]
    }

    if {$selection eq ""} {
      error [subst {
        The form page with item_id $item_id was not found in the
        xowiki_form_instance_item_index.  Consider 'DROP TABLE
        xowiki_form_instance_item_index CASCADE;' and restart server
        (the table is rebuilt automatically, but this could take a
        while, when the number of pages is huge).
      }]
    }

    $object mset [ns_set array $selection]

    if {$initialize} {
      $object initialize_loaded_object
    }
    return $object
  }
::xowiki::FormPage proc sql_value input {
    #
    # Transform wild-card * into SQL wild-card.
    #
    return [string map {* %} $input]
  }
::xowiki::FormPage proc get_form_entries {-base_item_ids:required -package_id:required -form_fields:required {-publish_status ready} {-parent_id "*"} {-extra_where_clause ""} {-h_where {tcl true h "" vars "" sql ""}} {-h_unless {tcl true h "" vars "" sql ""}} {-always_queried_attributes ""} {-orderby ""} {-page_size 20} {-page_number ""} {-initialize true} {-from_package_ids ""}} {
    #
    # Get query attributes for all tables (to allow e.g. sorting by time)
    #
    # The basic essential fields item_id, name, object_type and
    # publish_status are always automatically fetched from the
    # instance_select_query. Add the query attributes, we want to
    # obtain as well automatically.
    #
    # "-parent_id *"  means to get instances, regardless of
    # parent_id. Under the assumption, page_template constrains
    # the query enough to make it fast...
    #
    # "-from_package_ids {}" means get pages from the instance
    # provided via package_id, "*" means from all
    # packages. Furthermore, a list of package_ids can be given.
    #
    # "-always_queried_attributes *" means to obtain enough attributes
    # to allow a save operations etc. on the instances.
    #

    set sql_atts {
      item_id name publish_status object_type
      parent_id revision_id instance_attributes
      creation_date creation_user last_modified
      package_id title page_template state assignee
    }

    if {$always_queried_attributes eq "*"} {
      lappend sql_atts  object_type object_id  description publish_date mime_type nls_language text  creator page_order page_id  page_instance_id xowiki_form_page_id
    } else {
      foreach att $always_queried_attributes {
        set name [string range $att 1 end]
        lappend sql_atts $name
      }
    }

    #
    # Compute the list of field_names from the already covered sql
    # attributes
    #
    set covered_attributes [list _name _publish_status _item_id _object_type]
    foreach att $sql_atts {
      #regexp {[.]([^ ]+)} $att _ name
      lappend covered_attributes _$att
    }

    #
    # Collect SQL attributes from form_fields
    #
    foreach f $form_fields {
      if {![$f exists __base_field]} continue
      set field_name [$f name]
      if {$field_name in $covered_attributes} {
        continue
      }
      lappend sql_atts [$f set __base_field]
    }
    #:msg sql_atts=$sql_atts

    #
    # Build parts of WHERE clause
    #
    set publish_status_clause [::xowiki::Includelet publish_status_clause  -base_table "" $publish_status]
    #
    # Build filter clause (uses hstore if configured)
    #
    set filter_clause ""
    array set wc $h_where
    array set uc $h_unless
    set use_hstore [expr {[::xo::dc has_hstore] &&
                          [::$package_id get_parameter use_hstore:boolean 0]
                        }]
    #
    # Deactivating hstore optimization for now, must be further
    # completed and debugged before activating it again.
    #
    if {$wc(h) ne "" || $uc(h) ne ""} {
      ns_log notice "hstore available $use_hstore, but deactivating anyway for now (wc $wc(h) uc $uc(h) )"
    }

    set use_hstore 0
    if {$use_hstore} {
      if {$wc(h) ne ""} {
        set filter_clause " and '$wc(h)' <@ hkey"
      }
      if {$uc(h) ne ""} {
        set filter_clause " and not '$uc(h)' <@ hkey"
      }
    }
    if {$wc(sql) ne ""} {
      #:log "... wc SQL '$wc(sql)'"
      foreach filter $wc(sql) {
        append filter_clause " and $filter"
      }
    }
    if {$uc(sql) ne ""} {
      #:log "... uc SQL '$uc(sql)'"
      foreach filter $uc(sql) {
        append filter_clause " and not $filter"
      }
    }
    #:log filter_clause=$filter_clause

    #
    # Build package clause
    #
    if {$from_package_ids eq ""} {
      set package_clause "and package_id = :package_id"
    } elseif {$from_package_ids eq "*"} {
      set package_clause ""
    } elseif {[llength $from_package_ids] == 1} {
      set package_clause "and package_id = :from_package_ids"
    } else {
      set package_clause "and package_id in ([ns_dbquotelist $from_package_ids])"
    }

    if {$parent_id eq "*"} {
      # instance_select_query expects "" for all parents, but for the semantics
      # of this method, "*" looks more appropriate
      set parent_id ""
    }

    set parent_clause ""
    if {$parent_id ne ""} {
      set parent_clause " and parent_id = :parent_id"
    }

    if {[llength $base_item_ids] == 0} {
      error "base_item_ids must not be empty"
    }
    #
    # transform all into an SQL query
    #
    if {$page_number ne ""} {
      set limit $page_size
      set offset [expr {$page_size*($page_number-1)}]
    } else {
      set limit ""
      set offset ""
    }
    set sql [::xo::dc select  -vars [join $sql_atts ", "]  -from xowiki_form_instance_item_view  -where " page_template in ([ns_dbquotelist $base_item_ids])  $publish_status_clause $filter_clause $package_clause $parent_clause  $extra_where_clause"  -orderby $orderby  -limit $limit -offset $offset]
    #ns_log notice "get_form_entries:\n[string map [list :parent_id $parent_id :package_id $package_id] $sql]"

    #
    # When we query all attributes, we return objects named after the
    # item_id (like for single fetches)
    #
    set named_objects [expr {$always_queried_attributes eq "*"}]
    set items [::xowiki::FormPage instantiate_objects -sql $sql  -named_objects $named_objects -object_named_after "item_id"  -object_class ::xowiki::FormPage -initialize $initialize]

    #:log "$use_hstore wc tcl $wc(tcl) uc tcl $uc(tcl)"
    if {!$use_hstore && ($wc(tcl) != "true" || $uc(tcl) != "true")} {

      set init_vars $wc(vars)
      foreach p [$items children] {
        $p set __ia [dict merge $init_vars [$p instance_attributes]]

        if {$wc(tcl) != "true"} {
          if {![nsf::directdispatch $p -frame object ::expr $wc(tcl)]} {
            #:log "WC check '$wc(tcl)' [$p name] => where DELETE"
            $items delete $p
            continue
          }
        }
        if {$uc(tcl) != "true"} {
          if {[nsf::directdispatch $p -frame object ::expr $uc(tcl)]} {
            #:log "UC check '$uc(tcl)' on [$p name] => unless DELETE"
            $items delete $p
          }
        }
      }
    }
    return $items
  }
::xowiki::FormPage proc get_super_folders {package_id folder_id {aggregated_folder_refs {}}} {
    #
    # Compute the set of folder_refs configured in the referenced
    # folders.  Get first the folder_refs configured in the actual
    # folder, which are not yet in aggregated_folder_refs.
    #
    set additional_folder_refs ""
    set folder [::xo::db::CrClass get_instance_from_db -item_id $folder_id -revision_id 0]
    if {[$folder istype ::xowiki::FormPage]} {
      foreach ref [$folder property inherit_folders] {
        if {$ref ni $aggregated_folder_refs} {lappend additional_folder_refs $ref}
      }
    }
    #
    # Process the computed additional folder refs recursively to obtain
    # the transitive set of configured item_refs (pointing to folders).
    #
    lappend aggregated_folder_refs {*}$additional_folder_refs
    foreach item_ref $additional_folder_refs {
      set page [::$package_id get_page_from_item_ref $item_ref]
      if {$page eq ""} {error "configured inherited folder $item_ref cannot be resolved"}
      set aggregated_folder_refs  [FormPage get_super_folders $package_id [$page item_id] $aggregated_folder_refs]
    }
    return $aggregated_folder_refs
  }
::xowiki::FormPage proc get_all_children {-folder_id:required {-publish_status ready} {-object_types {::xowiki::Page ::xowiki::Form ::xowiki::FormPage}} {-extra_where_clause "1=1"} {-include_child_folders none} {-initialize true}} {

    set folder [::xo::db::CrClass get_instance_from_db -item_id $folder_id -revision_id 0]
    set package_id [$folder package_id]

    set publish_status_clause [::xowiki::Includelet publish_status_clause $publish_status]
    set result [::xo::OrderedComposite new -destroy_on_cleanup]
    $result set folder_ids ""

    set list_of_folders [list $folder_id]
    set inherit_folders [FormPage get_super_folders $package_id $folder_id]
    #:log inherit_folders=$inherit_folders

    foreach item_ref $inherit_folders {
      set folder [::xo::cc cache [list ::$package_id get_page_from_item_ref $item_ref]]
      if {$folder eq ""} {
        ad_log error "Could not resolve parameter folder page '$item_ref' of FormPage [self]."
      } else {
        lappend list_of_folders [$folder item_id]
      }
    }

    if {$include_child_folders eq "direct"} {
      #
      # Get all children of the current folder on the first level and
      # append it to the list_of_folders.
      #
      set folder_form [::$package_id instantiate_forms -forms en:folder.form]
      set child_folders [xo::dc list -prepare integer,integer get_child_folders {
        select item_id from xowiki_form_instance_item_index
        where parent_id = :folder_id
        and page_template = :folder_form
      }]
      foreach f $child_folders {
        ::xo::db::CrClass get_instance_from_db -item_id $f
      }
      lappend list_of_folders {*}$child_folders
    }

    $result set folder_ids $list_of_folders

    foreach folder_id $list_of_folders {
      foreach object_type $object_types {
        set attributes [list revision_id creation_user title parent_id page_order  "to_char(last_modified,'YYYY-MM-DD HH24:MI') as last_modified" ]
        set base_table [$object_type set table_name]i
        if {$object_type eq "::xowiki::FormPage"} {
          set attributes "bt.* $attributes"
        }
        set items [$object_type get_instances_from_db  -folder_id $folder_id  -with_subtypes false  -initialize $initialize  -select_attributes $attributes  -where_clause "$extra_where_clause $publish_status_clause"  -base_table $base_table]

        foreach i [$items children] {
          $result add $i
        }
      }
    }
    return $result
  }
::xowiki::FormPage proc get_table_form_fields {-base_item -field_names -form_constraints {-nls_language ""}} {

    set __att {publish_status 1}
    foreach att [list last_modified creation_user {*}[::xowiki::FormPage array names db_slot]] {
      dict set __att $att 1
    }

    # set cr_field_spec [::xowiki::PageInstance get_short_spec_from_form_constraints  #                            -name @cr_fields  #                            -form_constraints $form_constraints]
    # if some fields are hidden in the form, there might still be values (creation_user, etc)
    # maybe filter hidden? ignore for the time being.

    set cr_field_spec ""
    set field_spec [::xowiki::PageInstance get_short_spec_from_form_constraints  -name @fields  -form_constraints $form_constraints]

    foreach field_name $field_names {
      set short_spec [::xowiki::PageInstance get_short_spec_from_form_constraints  -name $field_name  -form_constraints $form_constraints]
      #:log "short_spec of $field_name <$short_spec> field_spec <$field_spec> cr_field_spec <$cr_field_spec>"

      switch -glob -- $field_name {
        __* {error not_allowed}
        _* {
          set varname [string range $field_name 1 end]
          if {![dict exists $__att $varname]} {
            error "unknown attribute $field_name"
          }
          #:log "create_raw_form_field of $field_name <$cr_field_spec,$short_spec>"
          set f [$base_item create_raw_form_field  -omit_field_name_spec true  -name $field_name  -slot [$base_item find_slot $varname]  -spec $cr_field_spec,$short_spec  -nls_language $nls_language  ]
          #:log "---> $f <[$f label]>"
          $f set __base_field $varname
        }
        default {
          set f [$base_item create_raw_form_field  -omit_field_name_spec true  -name $field_name  -slot ""  -spec $field_spec,$short_spec  -nls_language $nls_language  ]
        }
      }
      lappend form_fields $f
    }
    return $form_fields
  }
::xowiki::FormPage proc compute_filter_clauses {-unless -where} {

    set init_vars [list]
    set uc {tcl false h "" vars "" sql ""}
    if {[info exists unless]} {
      set uc [dict merge $uc [:filter_expression $unless ||]]
      set init_vars [list {*}$init_vars {*}[dict get $uc vars]]
    }
    set wc {tcl true h "" vars "" sql ""}
    if {[info exists where]} {
      set wc [dict merge $wc [:filter_expression $where &&]]
      set init_vars [list {*}$init_vars {*}[dict get $wc vars]]
    }
    return [list init_vars $init_vars uc $uc wc $wc]
  }
::xowiki::FormPage proc filter_expression {{-sql true} input_expr logical_op} {
    #ns_log notice "filter_expression '$input_expr' $logical_op"

    #
    # example for unless: wf_current_state = closed|accepted || x = 1
    #

    array set tcl_op {= eq < < > > >= >= <= <=}
    array set sql_op {= =  < < > > >= >= <= <=}
    array set op_map {
      contains,sql {$lhs_var like '%$sql_rhs%'}
      contains,tcl {{$rhs} in $lhs_var}
      matches,sql {$lhs_var like '$sql_rhs'}
      matches,tcl {[string match "$rhs" $lhs_var]}
    }

    set tcl_clause [list]
    set h_clause [list]
    set vars [list]
    set sql_clause [list]
    foreach clause [split [string map [list $logical_op \x00] $input_expr] \x00] {
      if {[regexp {^(.*[^<>])\s*([=<>]|<=|>=|contains|matches)\s*([^=]?.*)$} $clause _ lhs op rhs_expr]} {
        set lhs [string trim $lhs]
        set rhs_expr [string trim $rhs_expr]
        if {[string index $lhs 0] eq "_"} {
          #
          # Comparison with field names starting with "_"
          #
          set lhs_var [string range $lhs 1 end]
          set rhs [split $rhs_expr |]
          set sql_rhs [:sql_value $rhs]
          #:msg "check op '$op' in SQL [info exists op_map($op,sql)]"
          if {[info exists op_map($op,sql)]} {
            lappend sql_clause [subst -nocommands $op_map($op,sql)]
            if {[info exists :db_slot($lhs_var)]} {
              set lhs_var "\[set :$lhs_var\]"
              lappend tcl_clause [subst -nocommands $op_map($op,tcl)]
            } else {
              :msg "ignoring unknown variable '$lhs_var' in expression (have '[lsort [array names :db_slot]]')"
            }
          } elseif {[llength $rhs]>1} {
            lappend sql_clause "$lhs_var in ([ns_dbquotelist $rhs])"
            # the following statement is only needed, when we rely on tcl-only
            lappend tcl_clause "\[lsearch -exact {$rhs} \[:property $lhs\]\] > -1"
          } else {
            lappend sql_clause "$lhs_var $sql_op($op) '$rhs'"
            # the following statement is only needed, when we rely on tcl-only
            lappend tcl_clause "\[:property $lhs\] $tcl_op($op) {$rhs}"
          }
        } else {
          #
          # Field names referring to instance attributes.
          #
          set hleft [::xowiki::hstore::double_quote $lhs]
          lappend vars $lhs ""
          if {$op eq "contains"} {
            #make approximate query
            set lhs_var instance_attributes
            set sql_rhs $rhs_expr
            lappend sql_clause [subst -nocommands $op_map($op,sql)]
          }
          set lhs_var "\[dict get \$__ia $lhs\]"
          set tcl_rhs_clauses {}
          foreach rhs [split $rhs_expr |] {
            set sql_rhs [:sql_value $rhs]
            if {[info exists op_map($op,tcl)]} {
              lappend tcl_rhs_clauses [subst -nocommands $op_map($op,tcl)]
            } else {
              lappend tcl_rhs_clauses "$lhs_var $tcl_op($op) {$rhs}"
            }
            if {$op eq "="} {
              # TODO: think about a solution for other operators with
              # hstore maybe: extracting it by a query via hstore and
              # compare in plain SQL
              lappend h_clause "$hleft=>[::xowiki::hstore::double_quote $rhs]"
            }
          }
          lappend tcl_clause ([join $tcl_rhs_clauses ||])
        }
      } else {
        :msg "ignoring $clause"
      }
    }
    if {[llength $tcl_clause] == 0} {
      set tcl_clause [list true]
    }
    #:msg sql=$sql_clause,tcl=$tcl_clause
    set result [list  tcl [join $tcl_clause $logical_op]  h [join $h_clause ,]  vars $vars  sql $sql_clause]
    #:msg "filter_expression -sql $sql inp '$input_expr' log '$logical_op' -> $result"

    return $result
  }
::xowiki::FormPage proc get_folder_children {-folder_id:required {-publish_status ready} {-object_types {::xowiki::Page ::xowiki::Form ::xowiki::FormPage}} {-extra_where_clause true} {-initialize true}} {
    set publish_status_clause [::xowiki::Includelet publish_status_clause $publish_status]
    set result [::xo::OrderedComposite new -destroy_on_cleanup]

    foreach object_type $object_types {
      set attributes [list revision_id creation_user title parent_id page_order  "to_char(last_modified,'YYYY-MM-DD HH24:MI') as last_modified" ]
      set base_table [$object_type set table_name]i
      if {$object_type eq "::xowiki::FormPage"} {
        set attributes "bt.* $attributes"
      }
      set items [$object_type get_instances_from_db  -folder_id $folder_id  -with_subtypes false  -select_attributes $attributes  -where_clause "$extra_where_clause $publish_status_clause"  -base_table $base_table  -initialize $initialize]

      foreach i [$items children] {
        $result add $i
      }
    }
    return $result
  }
::xowiki::FormPage instproc lappend_property {name value} {
    #
    # lappend the specified value to the named property. If the
    # property does not exists, create a new one.
    #
    if {[:exists_property $name]} {
      :set_property $name [concat [:get_property -name $name$value]
    } else {
      :set_property -new 1 $name $value
    }
  }
::xowiki::FormPage instproc load_values_into_form_fields form_fields {
    set is_new [:is_new_entry ${:name}]

    foreach f $form_fields {
      set att [$f name]
      switch -glob $att {
        __* {}
        _* {
          set varname [string range $att 1 end]
          :combine_data_and_form_field_default $is_new $f [set :$varname]
        }
        default {
          #:log "load_values_into_form_field $att"  "exists [dict exists ${:instance_attributes} $att]"  "in [dict keys ${:instance_attributes}]"
          if {[dict exists ${:instance_attributes} $att]} {
            :combine_data_and_form_field_default $is_new $f [dict get ${:instance_attributes} $att]
          }
        }
      }
    }
  }
::xowiki::FormPage instproc condition=in_state {query_context value} {
    # possible values can be or-ed together (e.g. initial|final)
    foreach v [split $value |] {
      #:msg "check [:state] eq $v"
      if {[:state] eq $v} {return 1}
    }
    return 0
  }
::xowiki::FormPage instproc is_folder_page {{-include_folder_links true}} {
    #
    # Make sure, the page_template is instantiated
    #
    if {![nsf::is object ::${:page_template}]} {
      ::xo::db::CrClass get_instance_from_db -item_id ${:page_template}
    }
    set page_template_name [${:page_template} name]
    if {$page_template_name eq "en:folder.form"} {
      return 1
    } elseif {$include_folder_links && $page_template_name eq "en:link.form"} {
      set link_type [:get_property_from_link_page link_type]
      return [expr {$link_type eq "folder_link"}]
    } else {
      return 0
    }
  }
::xowiki::FormPage instproc notification_render {} {
    if {[:is_link_page] || [:is_folder_page]} {
      return ""
    } else {
      return [next]
    }
  }
::xowiki::FormPage instproc form_field_as_html {{-mode edit} before name form_fields} {
    set found 0
    foreach f $form_fields {
      if {[$f name] eq $name} {set found 1; break}
    }
    if {!$found} {
      set f [:create_raw_form_field -name $name -slot [:find_slot $name]]
    }
    #:log "found $name in $form_fields -> $found [$f info class]"

    if {$mode eq "edit" || [$f display_field]} {
      set html [$f asHTML]
    } else {
      set html @$name@
    }
    #:msg "RESULT: $name <$html>"
    return ${before}$html
  }
::xowiki::FormPage instproc is_form {} {
    return [:exists_property form_constraints]
  }
::xowiki::FormPage instproc initialize_loaded_object {} {
    #:msg "${:name} [:info class]"
    if {[info exists :page_template]} {
      set p [::xo::db::CrClass get_instance_from_db -item_id ${:page_template}]
      #
      # The Form might come from a different package type (e.g. a
      # workflow) make sure, the source package is available.
      #
      # Note that global pages (site_wide_pages) might not belong to
      # a package and have therefore an empty package_id.
      #
      set package_id [$p package_id]
      if {$package_id ne ""} {
        ::xo::Package require $package_id
      }
    }
    next
  }
::xowiki::FormPage instproc www-edit {{-validation_errors ""} {-disable_input_fields 0} {-view:boolean true}} {
    #:log "edit [self args]"

    :include_header_info -prefix form_edit
    if {[::xo::cc mobile]} {
      :include_header_info -prefix mobile
    }

    set form [:get_form]
    set anon_instances [:get_anon_instances]
    #:log form=$form
    #:log anon_instances=$anon_instances

    set field_names [:field_names -form $form]
    #:log field_names=$field_names
    set form_fields [:create_form_fields $field_names]
    #foreach f0 $form_fields {
    #  ns_log notice "... created ff [$f0 name] [$f0 info class] '[$f0 value]'"
    #}

    if {$form eq ""} {
      #
      # Since we have no form, we create it on the fly
      # from the template variables and the form field specifications.
      #
      set form "<form></form>"
      set formgiven 0
    } else {
      set formgiven 1
    }
    #:log formgiven=$formgiven

    # check name field:
    #  - if it is for anon instances, hide it,
    #  - if it is required but hidden, show it anyway
    #    (might happen, when e.g. set via @cr_fields ... hidden)
    set name_field [:lookup_form_field -name _name $form_fields]

    if {$anon_instances} {
      #$name_field config_from_spec hidden
    } else {
      if {[$name_field istype ::xowiki::formfield::hidden]
          && [$name_field required] == true
        } {
        $name_field config_from_spec text,required
        $name_field type text
      }
    }

    #
    # Include _text only, if explicitly needed (in form
    # needed(_text))".
    #
    if {![dict exists ${:__field_needed} _text]} {
      #:msg "setting text hidden"
      set f [:lookup_form_field -name _text $form_fields]
      $f config_from_spec hidden
    }

    if {[:exists_form_parameter __disabled_fields]} {
      #
      # Disable some form-fields since these are disabled in the form
      # as well.
      #
      foreach name [:form_parameter __disabled_fields:0..n] {
        set f [:lookup_form_field -name $name $form_fields]
        $f set_disabled true
      }
    }

    #:show_fields $form_fields
    #:log "__form_action [:form_parameter __form_action {}]"

    if {[:form_parameter __form_action ""] eq "save-form-data"} {
      #
      # We want to save the form data, so we have to validate.
      #
      #:log "we have to validate"
      #
      # In case we are triggered internally, we might not have a
      # a connection. Therefore, do not validate the CSRF token.
      #
      if {![::${:package_id} exists __batch_mode]} {
        security::csrf::validate
      }

      lassign [:get_form_data $form_fields] validation_errors category_ids
      if {$validation_errors != 0} {
        #
        # We have validation errors.
        #
        #:log "$validation_errors validation errors in $form_fields"
        #foreach f $form_fields { :log "$f: [$f name] '[$f set value]' err: [$f error_msg] " }
        #
        # In case we are triggered internally, we might not have a
        # a connection, so we don't present the form with the
        # error messages again, but we return simply the validation
        # problems.
        #
        if {[::${:package_id} exists __batch_mode]} {
          set errors [list]
          foreach f $form_fields {
            if {[$f error_msg] ne ""} {
              lappend errors [list field [$f name] value [$f set value] error [$f error_msg]]
            }
          }
          set evaluation_errors ""
          if {[::${:package_id} exists __evaluation_error]} {
            set evaluation_errors "\nEvaluation error: [::${:package_id} set __evaluation_error]"
            ::${:package_id} unset __evaluation_error
          }
          error "[llength $errors] validation error(s): $errors $evaluation_errors"
        }
        #
        # Reset the name in error cases to the original one.
        #
        set :name [:form_parameter __object_name:signed,convert]
      } else {
        #
        # We have no validation errors, so we can save the content.
        #
        :save_data  -use_given_publish_date [expr {"_publish_date" in $field_names}]  [::xo::cc form_parameter __object_name:signed,convert ""$category_ids

        #
        # The data might have references. Perform the rendering here to compute
        # the references instead on every view (which would be safer, but slower). This is
        # roughly the counterpart to edit_data and save_data in ad_forms.
        #
        set content [:render -update_references all]
        #:log "after save refs=[expr {[info exists :references]?${:references} : {NONE}}]"

        set redirect_method [:form_parameter __form_redirect_method:wordchar "view"]
        #:log "redirect_method $redirect_method"

        if {$redirect_method eq "__none"} {
          return
        } else {
          if {$redirect_method ne "view"} {
            set qp "?m=$redirect_method"
          } else {
            set qp ""
          }
          set url [:pretty_link]$qp
          #
          # The method query_parameter uses now "::xo::cc set_parameter ...."
          # with highest precedence
          #
          set return_url [::${:package_id} query_parameter return_url:localurl $url]

          #:log "${:name}: url=$url, return_url=$return_url"
          ::${:package_id} returnredirect $return_url

          return
        }
      }
    } elseif {[:form_parameter __form_action ""] eq "view-form-data"
              && ![info exists :__feedback_mode]
            } {
      #
      # We have nothing to save (maybe everything is read-only). Check
      # __feedback_mode to prevent recursive loops.
      #
      set redirect_method [:form_parameter __form_redirect_method:wordchar "view"]
      #:log "__redirect_method=$redirect_method"
      return [:www-view]
    } else {
      #
      # Build the input form and display the current values.
      #
      #:log "form_action is something different: <[:form_parameter __form_action {}]>"
      if {[:is_new_entry ${:name}]} {
        set :creator [::xo::get_user_name [::xo::cc user_id]]
        set :nls_language [::${:package_id} default_locale]
      }

      #array set __ia ${:instance_attributes}
      :load_values_into_form_fields $form_fields

      foreach f $form_fields {
        set ff([$f name]) $f
      }

      #
      # For named entries, just set the entry fields to empty,
      # without changing the instance variables
      #
      #:log "my is_new_entry ${:name} = [:is_new_entry ${:name}]"
      if {[:is_new_entry ${:name}]} {

        if {$anon_instances} {
          set basename [::xowiki::autoname basename [${:page_template} name]]
          set name [::xowiki::autoname new -name $basename -parent_id ${:parent_id}]
          #:log "generated name=$name, page_template-name=[${:page_template} name]"
          $ff(_name) value $name
        } else {
          $ff(_name) value [$ff(_name) default]
        }
        if {![$ff(_title) istype ::xowiki::formfield::hidden]} {
          $ff(_title) value [$ff(_title) default]
        }
        foreach param [list title detail_link:localurl text description] {
          regexp {^([^:]+):?} $param . var
          if {[:exists_query_parameter $var]} {
            set value [:query_parameter $param]
            switch -- $var {
              detail_link {
                set f [:lookup_form_field -name $var $form_fields]
                $f value [$f convert_to_external $value]
              }
              title - text - description {
                set f [:lookup_form_field -name _$var $form_fields]
              }
            }
            $f value [$f convert_to_external $value]
          }
        }
      }

      $ff(_name) set transmit_field_always 1
      $ff(_nls_language) set transmit_field_always 1
    }

    #
    # Some final sanity checks.
    #
    :form_fields_sanity_check $form_fields
    :post_process_form_fields $form_fields

    #
    # "dom parse -html" has two problems with ADP tags like "<adp:icon ...>":
    # a) If the tag name contains a colon or underscore, the tag is
    #    treated like plain text, i.e. "<" and ">" are converted into
    #    HTML entities.
    # b) These tags have to be closed "<adp:icon ...>" is invalid.
    #    Several existomg ADP tags have not closing tag.
    #
    # Therefore, we resolve the ADP tags before parsing the text by
    # tdom. There should be some framework support to do this in
    # general, but until we have this, resolve this problem here locally.
    #
    set form [::template::adp_parse_tags [:substitute_markup $form]]

    #
    # The following command would be correct, but does not work due to a bug in
    # tdom.
    # set form [:regsub_eval   #              [template::adp_variable_regexp] $form  #              {:form_field_as_html -mode edit "\\\1" "\2" $form_fields}]
    # Due to this bug, we program around and replace the at-character
    # by \x03 to avoid conflict with the input and we replace these
    # magic chars finally with the fields resulting from tdom.

    set form [string map [list @ \x03] $form]
    #:msg form=$form

    dom parse -html -- $form :doc
    ${:doc} documentElement :root

    if {${:root} eq ""} {
      error "form '$form' is not valid"
    }

    ::xo::require_html_procs
    ${:root} firstChild fcn
    #:msg "orig fcn $fcn, root ${:root} [${:root} nodeType] [${:root} nodeName]"

    set formNode [lindex [${:root} selectNodes //form] 0]
    if {$formNode eq ""} {
      :msg "no form found in page [${:page_template} name]"
      ns_log notice "no form found in page [${:page_template} name]\n$form"
      set rootNode ${:root}
      $rootNode firstChild fcn
    } else {
      set rootNode $formNode
      $rootNode firstChild fcn
      # Normally, the root node is the formNode, fcn is the first
      # child (often a TEXT_NODE), but ic can be even empty.
    }


    #
    # Prepend some fields above the HTML contents of the form.
    #
    $rootNode insertBeforeFromScript {
      ::html::div {
        ::html::input -type hidden -name __object_name -value [::security::parameter::signed ${:name}]
        ::html::input -type hidden -name __form_action -value save-form-data
        ::html::input -type hidden -name __current_revision_id -value ${:revision_id}
        :extra_html_fields
        ::html::CSRFToken
      }
      #
      # Insert automatic form fields on top.
      #
      foreach att $field_names {
        #if {$formgiven && ![string match _* $att]} continue
        if {[dict exists ${:__field_in_form} $att]} continue
        set f [:lookup_form_field -name $att $form_fields]
        #:log "insert auto_field $att $f ([$f info class])"
        $f render_item
      }
    } $fcn
    #
    # Append some fields after the HTML contents of the form.
    #
    set button_class(wym) ""
    set button_class(xinha) ""
    set has_file 0
    $rootNode appendFromScript {
      # append category fields
      foreach f $form_fields {
        #:msg "[$f name]: is wym? [$f has_instance_variable editor wym]"
        if {[string match "__category_*" [$f name]]} {
          $f render_item
        } elseif {[$f has_instance_variable editor wym]} {
          set button_class(wym) "wymupdate"
        } elseif {[$f has_instance_variable editor xinha]} {
          set button_class(xinha) "xinhaupdate"
        }
        if {[$f has_instance_variable type file]} {
          set has_file 1
        }
      }

      #
      # Add a submit field(s) at bottom.
      #
      :render_form_action_buttons -CSSclass [string trim "$button_class(wym) $button_class(xinha)"]
    }

    if {$formNode ne ""} {

      if {[:exists_query_parameter "return_url"]} {
        set return_url [:query_parameter return_url:localurl]
      } else {
        #
        # When no return_url is specified and we edit a page different
        # from the invoked page, we use the calling page for default
        # redirection.  We do not want to redirect to some "embedded"
        # object after the edit. This happens if one edits e.g. a page
        # through a link.
        #
        if {[::xo::cc exists invoke_object]
            && [::xo::cc invoke_object] ne [self]
          } {
          #:log "=== no return_url specified, using [::xo::cc url] or [[::${:package_id} context] url]"
          set return_url [::xo::cc url]
          set return_url [ad_urlencode_url $return_url]
        }
      }
      set m [:form_parameter __form_redirect_method:wordchar "edit"]
      set url [export_vars -no_base_encode -base [:action_url] {m return_url}]
      #:log "=== setting action <$url> for form-action my-name ${:name}"
      $formNode setAttribute action $url method POST role form
      if {$has_file} {$formNode setAttribute enctype multipart/form-data}
      Form add_dom_attribute_value $formNode class [${:page_template} css_class_name]
    }

    :set_form_data $form_fields
    if {$disable_input_fields} {
      #
      # (a) Disable explicit input fields.
      #
      foreach f $form_fields {$f set_disabled true}
      #
      # (b) Disable input in HTML-specified fields.
      #
      set disabled [Form dom_disable_input_fields $rootNode]
      #
      # Collect these variables in a hidden field to be able to
      # distinguish later between e.g. un unchecked checkmark and an
      # disabled field. Maybe, we have to add the fields from case (a)
      # as well.
      #
      $rootNode appendFromScript {
        ::html::input -type hidden -name "__disabled_fields" -value $disabled
      }
    }
    :post_process_dom_tree ${:doc} ${:root} $form_fields

    set html [${:root} asHTML]
    set html [:regsub_eval   {(^|[^\\])\x03([[:alnum:]_:]+)\x03} $html  {:form_field_as_html -mode edit "\\\1" "\2" $form_fields}]
    #
    # Replace unbalanced @ characters.
    #
    set html [string map [list \x03 @] $html]

    #
    # Handle unreported errors (in the future...). Unreported errors
    # might occur, when a form-field was rendered above without
    # "render_item". This can happen with inline rendering of the
    # input fields where validation errors occur. Inline rendering
    # happens very seldom (I know not a single occurrence in the
    # wild). For such cases, one should define an extra field in the
    # form with an idea, reparse the tree and insert the errors
    # there. But first look, if we find a single occurrence.
    #
    set unprocessed {}
    foreach f $form_fields {
      if {[$f set error_msg] ne ""
          && ![$f exists error_reported]
        } {
        ns_log notice "form-field [$f name] has unprocessed error msg '[$f set error_msg]'"
        #$f render_error_msg
        lappend unprocessed [$f name]
      }
    }
    #ns_log notice "=============== $unprocessed unprocessed error messages"
    if {[llength $unprocessed] > 0} {
      ad_log warning "form has [llength $unprocessed] unprocessed "  "error messages in fields $unprocessed"
    }

    #:log "calling VIEW with HTML [string length $html]"
    if {$view} {
      :www-view $html
    } else {
      return $html
    }
  }
::xowiki::FormPage instproc set_form_data form_fields {
    ::xo::require_html_procs

    foreach f $form_fields {
      set att [$f name]
      # just handle fields of the form entry
      if {![dict exists ${:__field_in_form} $att]} continue
      #:msg "set form_value to form-field $att [dict exists ${:instance_attributes} $att]"
      if {[dict exists ${:instance_attributes} $att]} {
        #:msg "my set_form_value from ia $att '[dict get ${:instance_attributes} $att]', external='[$f convert_to_external [dict get ${:instance_attributes} $att]]' f.value=[$f value]"
        :set_form_value $att [$f convert_to_external [dict get ${:instance_attributes} $att]]
      } else {
        # do we have a value in the form? If yes, keep it.
        set form_value [:get_form_value $att]
        #:msg "no instance attribute, set form_value $att '[$f value]' form_value=$form_value"
        if {$att eq ""} {
          # we have no instance attributes, use the default value from the form field
          :set_form_value $att [$f convert_to_external [$f value]]
        }
      }
    }
  }
::xowiki::FormPage instproc map_value {map_type value} {
    :log "map_value $map_type$value"
    if {$map_type eq "category" && $value ne ""} {
      #
      # map a category item
      #
      return [dict get ${:__category_map} $value]
    } elseif {$map_type eq "party_id" && $value ne ""} {
      #
      # map a party_id
      #
      return [:map_party -property $map_type $value]
    } elseif {$map_type eq "file" && [llength $value] % 2 == 0} {
      #
      # drop revision_id from file value
      #
      set result {}
      foreach {a v} $value {
        if {$a eq "revision_id"} continue
        lappend result $a $v
      }
      return $result
    } else {
      return $value
    }
  }
::xowiki::FormPage instproc create_form_field {{-cr_field_spec ""} {-field_spec ""} field_name} {
    if {$cr_field_spec eq ""} {set cr_field_spec [:get_short_spec @cr_fields]}
    if {$field_spec eq ""} {set field_spec [:get_short_spec @fields]}
    return [next -cr_field_spec $cr_field_spec -field_spec $field_spec $field_name]
  }
::xowiki::FormPage instproc get_anon_instances {} {
    # maybe overloaded from WorkFlow
    :get_from_template anon_instances f
  }
::xowiki::FormPage instproc create_form_fields_from_names {-lookup:switch -set_values:switch -form_constraints field_names} {
    #
    # Create form-fields from field names. When "-lookup" is
    # specified, the code tries to reuseexisting form-field instead of
    # creating/recreating it.
    #
    # Since create_raw_form_field uses destroy_on_cleanup, we do not
    # have to care here about destroying the objects.
    #
    set form_fields {}
    foreach field_name $field_names {
      if {$lookup && [:form_field_exists $field_name]} {
        #:msg "... found form_field for $field_name"
        lappend form_fields [:lookup_form_field -name $field_name {}]
      } else {
        #:msg "create '$spec_name' with spec '$short_spec'"
        lappend form_fields [:create_raw_form_field  -name $field_name  -form_constraints $form_constraints  ]
      }
    }
    if {$set_values} {
      :load_values_into_form_fields $form_fields
    }
    return $form_fields
  }
::xowiki::FormPage instproc post_process_form_fields form_fields {
    # We offer here the possibility to iterate over the form fields
    # before they are rendered
  }
::xowiki::FormPage instproc create_form_fields field_names {
    set form_fields [:create_category_fields]
    foreach att $field_names {
      if {[string match "__*" $att]} continue

      if {[:form_field_exists $att]} {
        #ns_log notice "... found form-field $att"
        lappend form_fields [:lookup_form_field -name $att {}]

      } else {
        #ns_log notice "... create form-field for $att"
        lappend form_fields [:create_form_field  -cr_field_spec [:get_short_spec @cr_fields]  -field_spec [:get_short_spec @fields] $att]
      }
    }
    return $form_fields
  }
::xowiki::FormPage instproc map_values {map_type values} {
    # Map a list of values (for multi-valued form fields)
    # :log "map_values $map_type, $values"
    set mapped_values [list]
    foreach value $values {lappend mapped_values [:map_value $map_type $value]}
    return $mapped_values
  }
::xowiki::FormPage instproc set_publish_status value {
    if {$value ni {production ready}} {
      error "invalid value '$value'; use 'production' or 'ready'"
    }
    set :publish_status $value
  }
::xowiki::FormPage instproc adp_subst content {
    # Get the default field specs once and pass it to every field creation
    set field_spec [:get_short_spec @fields]
    set cr_field_spec [:get_short_spec @cr_fields]
    # Iterate over the variables for substitution
    set content [:regsub_eval -noquote true  [template::adp_variable_regexp$content"  {:get_value -field_spec $field_spec -cr_field_spec $cr_field_spec "\\\1" "\2"}]
    return [string range $content 1 end]
  }
::xowiki::FormPage instproc render_form_action_buttons {{-CSSclass ""}} {
    set f [::xowiki::formfield::submit_button new  -name __form_button_ok  -CSSclass $CSSclass  -destroy_on_cleanup ]

    ::html::div [expr {[$f exists form_button_wrapper_CSSclass]
                       ? [list class [$f form_button_wrapper_CSSclass]]
                       : {} }] {
                         $f render_input
                       }
  }
::xowiki::FormPage instproc set_content text {
    if {$text eq ""} {
      set :text $text
    } else {
      next
    }
  }
::xowiki::FormPage instproc reverse_map_values {-creation_user -create_user_ids map_type values category_ids_name} {
    # Apply reverse_map_value to a list of values (for multi-valued
    # form fields)
    :upvar $category_ids_name category_ids
    set mapped_values [list]
    foreach value $values {
      lappend mapped_values [:reverse_map_value  -creation_user $creation_user -create_user_ids $create_user_ids  $map_type $value category_ids]
    }
    return $mapped_values
  }
::xowiki::FormPage instproc render_icon {} {
    set page_template ${:page_template}
    if {[$page_template istype ::xowiki::FormPage]} {
      return [list text [$page_template property icon_markup] is_richtext true]
    }
    switch [$page_template name] {
      en:folder.form {
        return {text "<a title='folder' class='folder-open-icon'>&nbsp;</a>" is_richtext true}
      }
      en:link.form {
        set link_type [:get_property_from_link_page link_type "unresolved"]
        if {$link_type eq "unresolved"} {
          return {text "<a title='broken link' class='broken-link-icon'>&nbsp;</a>" is_richtext true}
        } else {
          return {text "<a title='link' class='link-icon'>&nbsp;</a>" is_richtext true}
        }
      }
      default {
        return [list text [$page_template title] is_richtext false]
      }
    }
  }
::xowiki::FormPage instproc get_form_constraints {{-trylocal false}} {
    #
    # This method os likely to be overloaded, maybe by xowf.
    #
    #:msg "is_form=[:is_form]"
    if {$trylocal && [:is_form]} {
      return [:property form_constraints]
    } else {
      #:msg "get_form_constraints returns '[:get_from_template form_constraints]'"
      return [:get_from_template form_constraints]
    }
  }
::xowiki::FormPage instproc render_content {} {
    #
    # Produce an HTML rendering from the FormPage.
    #
    #set package_id ${:package_id}
    :include_header_info -prefix form_view
    if {[::xo::cc mobile]} {
      :include_header_info -prefix mobile
    }
    set text [:get_from_template text]
    if {$text ne ""} {
      catch {set text [lindex $text 0]}
    }
    if {$text ne ""} {
      #:log "we have a template text='$text'"
      #
      # We have a template, this is the first preference.
      #
      set HTML [next]
    } else {
      #:log "we have a form '[:get_form]'"
      #
      # Fall back to the form, fill it out and compute HTML from this.
      #
      set form [:get_form]
      if {$form eq ""} {
        return ""
      }

      lassign [:field_names_from_form -form $form] form_vars field_names
      set :__field_in_form ""
      if {$form_vars} {
        foreach v $field_names {
          dict set :__field_in_form $v 1
        }
      }
      set form_fields [:create_form_fields $field_names]
      foreach n $field_names f $form_fields {
        dict set :__form_fields $n $f
      }

      :load_values_into_form_fields $form_fields

      # deactivate form-fields and do some final sanity checks
      foreach f $form_fields {$f set_disabled 1}
      :form_fields_sanity_check $form_fields
      :post_process_form_fields $form_fields

      set form [:regsub_eval   [template::adp_variable_regexp$form  {:form_field_as_html -mode display "\\\1" "\2" $form_fields}]

      # we parse the form just for the margin-form.... maybe regsub?
      dom parse -html -- $form :doc
      ${:doc} documentElement :root
      set form_node [lindex [${:root} selectNodes //form] 0]

      Form add_dom_attribute_value $form_node role form
      Form add_dom_attribute_value $form_node class [${:page_template} css_class_name]
      # The following two commands are for non-generated form contents
      :set_form_data $form_fields
      Form dom_disable_input_fields ${:root}
      # Return finally the result
      set HTML [${:root} asHTML]
    }

    return $HTML
  }
::xowiki::FormPage instproc condition=is_true {query_context value} {
    #
    # This condition maybe called from the policy rules.
    # The passed value is a tuple of the form
    #     {property-name operator property-value}
    #
    lassign $value property_name op property_value
    if {![info exists property_value]} {
      return 0
    }

    #:log "$value => [:adp_subst $value]"
    array set wc [::xowiki::FormPage filter_expression [:adp_subst $value] &&]
    #:log "wc= [array get wc]"
    set __ia [dict merge $wc(vars) [:instance_attributes]]
    #:log "expr $wc(tcl) returns => [expr $wc(tcl)]"
    return [expr $wc(tcl)]
  }
::xowiki::FormPage instproc update_item_index {} {
    :instvar name item_id package_id parent_id publish_status  page_template instance_attributes assignee state

    set useHstore [::$package_id get_parameter use_hstore:boolean 0]
    set updateVars {name = :name, package_id = :package_id,
      parent_id = :parent_id, publish_status = :publish_status,
      page_template = :page_template, assignee = :assignee,
      state = :state}

    if {$useHstore} {
      set hkey [::xowiki::hstore::dict_as_hkey [:hstore_attributes]]
      append updateVars ", hkey = '$hkey'"
    }

    set rows [xo::dc dml update_xowiki_form_instance_item_index [subst {
      update xowiki_form_instance_item_index
      set $updateVars
      where item_id = :item_id
    }]]

    if {$rows ne "" && $rows < 1} {
      set insertVars {item_id, name, package_id, parent_id, publish_status,
        page_template, assignee, state
      }
      set insertValues {:item_id, :name, :package_id, :parent_id, :publish_status,
        :page_template, :assignee, :state
      }
      if {$useHstore} {
        append insertVars {, hkey}
        append insertValues ", '$hkey'"
      }

      ::xo::dc dml insert_xowiki_form_instance_item_index [subst {
        insert into xowiki_form_instance_item_index
        ($insertVars) values ($insertValues)
      }]
    }
  }
::xowiki::FormPage instproc set_property {{-new 0} name value} {
    if {[string match "_*" $name]} {
      set key [string range $name 1 end]

      if {!$new && ![info exists :$key]} {
        error "property '$name' ($key) does not exist.  you might use flag '-new 1' for set_property to create new properties"
      }
      set :$key $value

    } else {

      if {!$new && ![dict exists ${:instance_attributes} $name]} {
        error "property '$name' does not exist.  you might use flag '-new 1' for set_property to create new properties"
      }
      dict set :instance_attributes $name $value
    }
    return $value
  }
::xowiki::FormPage instproc group_require {} {
    #
    # Create a group if necessary associated to the current form
    # page. Since the group_names are global, the group name contains
    # the parent_id of the FormPage.
    #
    set group_name "fpg-${:parent_id}-${:name}"
    set group_id [group::get_id -group_name $group_name]
    if {$group_id eq ""} {
      # group::new does not flush the cache - sigh!  Therefore, we have
      # to flush the old cache entry here manually.
      ::acs::clusterwide ns_cache flush util_memoize  "group::get_id_not_cached -group_name $group_name -subsite_id {} -application_group_id {}"
      set group_id [group::new -group_name $group_name]
    }
    return $group_id
  }
::xowiki::FormPage instproc www-toggle-modebutton {} {
    #
    # Check, if this function was called via POST
    #
    if {[ns_conn method] ne "POST"} {
      error "method should be called via POST"
    }

    #
    # Get the toggle name. Modebuttons are named like:
    #
    #    ::xowiki::mode::admin
    #
    set button [ns_queryget button admin]
    ::xowiki::mode::$button toggle
    ns_return 200 text/plain ok
  }
::xowiki::FormPage instproc update_attribute_from_slot {-revision_id slot:object value} {
    #
    # Perform first the regular operations.
    #
    next
    #
    # Make sure to update update_item_index when the attribute is
    # contained in the xowiki_form_instance_item_index.
    #
    set colName [$slot column_name]

    if {$colName in {
      package_id
      parent_id
      publish_status
      page_template
      assignee
      state
    }} {
      ::xowiki::update_item_index -item_id ${:item_id} -$colName $value
    } elseif {
              $colName eq "instance_attributes"
              && [::xo::dc has_hstore]
              && [::${:package_id} get_parameter use_hstore:boolean 0]
            } {
      ::xowiki::update_item_index -item_id ${:item_id} -hstore_attributes $value
    }
  }
::xowiki::FormPage instproc update {} {
      ::xo::dc transaction {
        next
        :instvar object_id state assignee
        ::xo::dc dml update_xowiki_form_page {update xowiki_form_page
          set state = :state,assignee = :assignee where xowiki_form_page_id = :object_id
        }
      }
    }
::xowiki::FormPage instproc is_link_page {} {
    #
    # Make sure, the page_template is instantiated
    #
    if {![nsf::is object ::${:page_template}]} {
      ::xo::db::CrClass get_instance_from_db -item_id ${:page_template}
    }
    return [expr {[${:page_template} name] eq "en:link.form"}]
  }
::xowiki::FormPage instproc extra_html_fields {} {
    return ""
  }
::xowiki::FormPage instproc langstring {attname lang {default {}}} {
    set result $default
    if {[:exists_property langstring]} {
      set d [:property langstring]
      if {[dict exists $d $attname $lang]} {
        set result [dict get $d $attname $lang]
      }
    }
    return $result
  }
::xowiki::FormPage instproc post_process_dom_tree {dom_doc dom_root form_fields} {
    # Part of the input fields comes from HTML, part comes via $form_fields
    # We offer here the possibility to iterate over the dom tree before it
    # is presented; can be overloaded
  }
::xowiki::FormPage instproc exists_property name {
    if {[regexp {^_([^_].*)$} $name _ varname]} {
      return [info exists :$varname]
    }
    return [dict exists ${:instance_attributes} $name]
  }
::xowiki::FormPage instproc setCSSDefaults {} {
    ad_log warning "deprecated method setCSSDefaults was called. The call should be removed"
  }
::nsf::method::property ::xowiki::FormPage  setCSSDefaults deprecated true
::xowiki::FormPage instproc demarshall {-parent_id -package_id -creation_user {-create_user_ids 0}} {
    # reverse map assignees
    :reverse_map_party_attribute -attribute assignee -create_user_ids $create_user_ids
    #
    # The function will compute the category_ids, which are were used
    # to categorize these objects in the source instance.
    set category_ids [list]

    #:msg "${:name} check cm=[info exists ::__xowiki_reverse_category_map] && iam=[info exists :__instance_attribute_map]"

    if {[info exists ::__xowiki_reverse_category_map]
        && [info exists :__instance_attribute_map]
      } {
      #:msg "we have a instance_attribute_map"

      #
      # replace all symbolic category values by the mapped IDs
      #
      set ia [list]
      array set use ${:__instance_attribute_map}
      array set multiple_index [list category 2 party_id 1 file 1]
      foreach {name value} [:instance_attributes] {
        #:msg "use($name) --> [info exists use($name)]"
        if {[info exists use($name)]} {
          #:msg "try to map value '$value' (category tree: $use($name))"
          set map_type [lindex $use($name) 0]
          set multiple [lindex $use($name) $multiple_index($map_type)]
          if {$multiple eq ""} {set multiple 1}
          if {$multiple} {
            lappend ia $name [:reverse_map_values  -creation_user $creation_user -create_user_ids $create_user_ids  $map_type $value category_ids]
          } else {
            lappend ia $name [:reverse_map_value  -creation_user $creation_user -create_user_ids $create_user_ids  $map_type $value category_ids]
          }
        } else {
          # nothing to map
          lappend ia $name $value
        }
      }
      set :instance_attributes $ia
      #:msg  "${:name} saving instance_attributes $ia"
    }
    set r [next]
    set :__category_ids [lsort -unique $category_ids]
    return $r
  }
::xowiki::FormPage instproc field_names {{-form ""}} {
    #ns_log notice "=== field_names form <$form>"
    #
    # Ge the field-names mentioned in form (the provided form has
    # always highest precedence).
    #
    lassign [:field_names_from_form -form $form] form_vars needed_attributes
    #
    # In case, we have no form, get the field-names from the form
    # constraints.
    #
    if {[llength $needed_attributes] == 0} {
      set needed_attributes [:field_names_from_form_constraints]
    }
    #:log "form=$form, form_vars=$form_vars needed_attributes=$needed_attributes"

    set :__field_in_form ""
    set :__field_needed ""
    if {$form_vars} {
      foreach v $needed_attributes {
        dict set :__field_in_form $v 1
      }
    }
    foreach v $needed_attributes {
      dict set :__field_needed $v 1
    }

    #
    # Remove the fields already included in auto_fields from the needed_attributes.
    # The final list "field_names" determines the order of the fields in the form.
    #
    set auto_fields [list _name _page_order _title _creator _assignee _text _description _nls_language]
    set reduced_attributes $needed_attributes

    foreach f $auto_fields {
      set p [lsearch -exact $reduced_attributes $f]
      if {$p > -1} {
        set reduced_attributes [lreplace $reduced_attributes $p $p]
      }
    }
    #:msg reduced_attributes(after)=$reduced_attributes
    #:msg fields_from_form=[dict keys ${:__field_in_form}]

    set field_names _name
    if {[::${:package_id} show_page_order]}  {
      lappend field_names _page_order
    }
    lappend field_names _title _creator _assignee
    foreach fn $reduced_attributes {
      lappend field_names $fn
    }
    foreach fn {_text _description _nls_language} {
      lappend field_names $fn
    }
    #:msg final-field_names=$field_names
    return $field_names
  }
::xowiki::FormPage instproc action_url {} {
    #
    # Can be overloaded.
    #
    return [:pretty_link]
  }
::xowiki::FormPage instproc pretty_name {} {
    set anon_instances [:get_from_template anon_instances f]
    if {$anon_instances} {
      return ${:title}
    }
    return ${:name}
  }
::xowiki::FormPage instproc configure_page=regression_test name {
    set :description "foo"
  }
::xowiki::FormPage instproc set_form_value {att value} {
    #:msg "set_form_value '$att' to '$value'"
    #
    # Feed the provided value into an HTML form provided via the
    # instance variable root.
    #
    set fields [${:root} selectNodes "//form//*\[@name='$att'\]"]
    #:msg "found field = $fields xp=//*\[@name='$att'\]"

    foreach field $fields {
      #
      # We handle textarea and input fields
      #
      if {[$field nodeName] eq "textarea"} {
        #
        # For TEXTAREA, delete the existing content and insert the new
        # content as text
        #
        foreach node [$field childNodes] {$node delete}
        $field appendFromScript {::html::t $value}
      }
      if {[$field nodeName] ne "input"} continue
      #
      # We handle now only INPUT types, but we have to differentiate
      # between different kinds of inputs.
      #
      set type [expr {[$field hasAttribute type] ? [$field getAttribute type] : "text"}]
      # the switch should be really different objects ad classes...., but that's HTML, anyhow.
      switch -- $type {
        checkbox {
          #:msg "$att: CHECKBOX value='$value', [$field hasAttribute checked], [$field hasAttribute value]"
          if {[$field hasAttribute value]} {
            set form_value [$field getAttribute value]
            #:msg "$att: form_value=$form_value, my value=$value"
            if {$form_value in $value} {
              $field setAttribute checked true
            } elseif {[$field hasAttribute checked]} {
              $field removeAttribute checked
            }
          } else {
            #:msg "$att: CHECKBOX entry has no value"
            if {[catch {set f [expr {$value ? 1 : 0}]}]} {set f 1}
            if {$value eq "" || $f == 0} {
              if {[$field hasAttribute checked]} {
                $field removeAttribute checked
              }
            } else {
              $field setAttribute checked true
            }
          }
        }
        radio {
          set inputvalue [$field getAttribute value]
          #:msg "radio: compare input '$inputvalue' with '$value'"
          if {$inputvalue eq $value} {
            $field setAttribute checked true
          }
        }
        hidden -
        password -
        text {
          if { ![$field getAttribute rep "0"] } {
            $field setAttribute value $value
          }
        }
        default {
          #:log "can't handle $type so far $att=$value"
        }
      }
    }
  }
::xowiki::FormPage instproc get_property {-source -name:required {-default ""}} {
    if {![info exists source]} {
      set page [self]
    } else {
      set page [:resolve_included_page_name $source]
    }
    return [$page property $name $default]
  }
::xowiki::FormPage instproc get_value {{-field_spec ""} {-cr_field_spec ""} before varname} {
    #
    # Read a property (instance attribute) and return
    # its pretty value in variable substitution.
    #
    # We check for special variable names here (such as current_user
    # or current_url). We provide a value from the current connection
    # context.
    if {$varname eq "current_user"} {
      set value [::xo::cc set untrusted_user_id]

    } elseif {$varname eq "current_url"} {
      set value [::xo::cc url]

    } else {
      #
      # First check to find an existing form-field with that name
      #
      set f [::xowiki::formfield::FormField get_from_name [self$varname]
      if {$f ne ""} {
        #
        # The form field exists already, we just fill in the actual
        # value (needed e.g. in weblogs, when the same form field is
        # used for multiple page instances in a single request)
        #
        set value [$f value [:property $varname]]
      } else {
        #
        # create a form-field from scratch
        #
        set value [:property $varname]
        set f [:create_form_field -cr_field_spec $cr_field_spec -field_spec $field_spec $varname]
        $f value $value
      }

      if {[$f hide_value]} {
        set value ""
      } elseif {![$f exists show_raw_value]} {
        set value [$f pretty_value $value]
      }
    }
    return $before$value
  }
::xowiki::FormPage instproc field_names_from_form {{-form ""}} {
    #
    # This method returns the form attributes (including _*).
    #
    set allvars [list {*}[[:info class] array names db_slot]  {*}[::xo::db::CrClass set common_query_atts]]

    set template [:get_html_from_content [:get_from_template text]]
    #:msg template=$template

    #set field_names [list _name _title _description _creator _nls_language _page_order]
    set field_names [list]
    if {$form eq ""} {set form [:get_form]}
    if {$form eq ""} {
      foreach {var _} [:template_vars $template] {
        #if {[string match _* $var]} continue
        if {$var ni $allvars && $var ni $field_names} {
          lappend field_names $var
        }
      }
      set from_HTML_form 0
    } else {
      foreach {match 1 att} [regexp -all -inline [template::adp_variable_regexp$form] {
        #if {[string match _* $att]} continue
        lappend field_names $att
      }
      #ns_log notice "field_names_from_form: [:serialize]"
      dom parse -html -- $form doc
      $doc documentElement root
      set fields [$root selectNodes "//*\[@name != ''\]"]
      foreach field $fields {
        set node_name [$field nodeName]
        if {$node_name ne "input"
            && $node_name ne "textarea"
            && $node_name ne "select"
          } continue
        set att [$field getAttribute name]
        #if {[string match _* $att]} continue
        if {$att ni $field_names} { lappend field_names $att }
      }
      set from_HTML_form 1
    }
    return [list $from_HTML_form $field_names]
  }
::xowiki::FormPage instproc render_thumbnails upload_info {
    return "[dict get $upload_info file_name] created"
  }
::xowiki::FormPage instproc form_fields_sanity_check form_fields {
    foreach f $form_fields {
      if {[$f is_disabled]} {
        # don't mark disabled fields as required
        if {[$f required]} {
          $f required false
        }
        #don't show the help-text, if you cannot input
        if {[$f help_text] ne ""} {
          $f help_text ""
        }
      }
      if {[$f exists transmit_field_always]
          && "::xowiki::formfield::omit" in [$f info mixin]} {
        # Never omit these fields, this would cause problems with
        # autonames and empty languages. Set these fields to hidden
        # instead.
        $f remove_omit
        $f class ::xowiki::formfield::hidden
        $f initialize
        #:msg "$f [$f name] [$f info class] [$f info mixin]"
      }
    }
  }
::xowiki::FormPage instproc footer {} {
    if {[info exists :__no_form_page_footer]} {
      next
    } else {
      set is_form [:property is_form__ 0]
      if {[:is_form]} {
        return [:include [list form-menu -form_item_id ${:item_id}  -buttons [list new answers [list form ${:page_template}]]]]
      } else {
        return [:include [list form-menu -form_item_id ${:page_template} -buttons form]]
      }
    }
  }
::xowiki::FormPage instproc new_link {-object_type -name -title -nls_language -parent_id -return_url page_package_id} {
    if {[info exists object_type]} {
      next
    } else {
      set template_id ${:page_template}
      if {![info exists parent_id]} {
        set parent_id [::$page_package_id folder_id]
      }
      set form [::$page_package_id pretty_link -parent_id $parent_id [::$template_id name]]
      return [::$page_package_id make_link -link $form $template_id  create-new return_url name title nls_language]
    }
  }
::xowiki::FormPage instproc get_parameter {attribute {default {}}} {
    #
    # Try to get the parameter from the parameter_page provided as
    # property "ParameterPages".
    #
    set value [::${:package_id} get_parameter_from_parameter_page  -parameter_page_name [:property ParameterPages]  $attribute]
    if {$value eq {}} {set value [next $attribute $default]}
    return $value
  }
::xowiki::FormPage instproc combine_data_and_form_field_default {is_new form_field data_value} {
    set form_field_value [$form_field value]
    if {$is_new && $form_field_value ne "" && $data_value eq ""} {
      #
      # On fresh entries, take the default value in case the old
      # value is blank.
      #
    } else {
      #
      # Reset for form field value to the external
      # representation of the data value.
      #
      $form_field value [$form_field convert_to_external $data_value]
    }
    #ns_log notice "combine_data_and_form_field_default $is_new form_field [$form_field name] data_value <$data_value> final <[$form_field value]>"
  }
::xowiki::FormPage instproc hstore_attributes {} {
    # Per default, we save all instance attributes in hstore, but a
    # subclass/object might have different requirements.
    return ${:instance_attributes}
  }
::xowiki::FormPage instproc www-file-upload {} {

    if {[ns_conn method] ne "POST"} {
      error "method should be called via POST"
    }

    #
    # Get the disposition via query parameter.  We have currently the
    # following disposition classes defined (see
    # xowiki-uploader-procs.tcl)
    #
    #   - ::xowiki::UploadFile
    #   - ::xowiki::UploadPhotoForm
    #   - ::xowiki::UploadFileIconified
    #
    ::security::csrf::validate

    set disposition [:query_parameter disposition:wordchar File]

    #
    # Filename is sanitized. If the filename contains only invalid
    # characters, "ad_sanitize_filename" might return empty, and we
    # complain.
    #
    set fileName [ad_sanitize_filename  [ns_queryget name [ns_queryget upload]]]
    if {[string length $fileName] == 0} {
      ad_return_complaint 1 [_ acs-templating.Invalid_filename]
      ad_script_abort
    }

    set dispositionClass ::xowiki::UploadFile
    if {[info commands ::xowiki::Upload$disposition] ne ""} {
      set dispositionClass ::xowiki::Upload$disposition
    }

    #ns_log notice "disposition class '$dispositionClass'"
    set dispositionObject [$dispositionClass new  -file_name $fileName  -content_type [ns_queryget upload.content-type]  -tmpfile [ns_queryget upload.tmpfile]  -parent_object [self]]
    set result [$dispositionObject store_file]
    $dispositionObject destroy
    ns_return [dict get $result status_code] text/plain [dict get $result message]
    ad_script_abort
  }
::xowiki::FormPage instproc property {name {default {}}} {
    if {[regexp {^_([^_].*)$} $name _ varname]} {
      if {[info exists :$varname]} {
        return [set :$varname]
      }
    } elseif {[dict exists ${:instance_attributes} $name]} {
      return [dict get ${:instance_attributes} $name]
    }
    return $default
  }
::xowiki::FormPage instproc reverse_map_value {-creation_user -create_user_ids map_type value category_ids_name} {
    # Perform the inverse function of map_value. During export, internal
    # representations are exchanged by string representations, which are
    # mapped here again to internal representations
    :upvar $category_ids_name category_ids
    if {[info exists ::__xowiki_reverse_category_map($value)]} {
      #:msg "map value '$value' (category tree: $use($name)) of ${:name} to an ID"
      lappend category_ids $::__xowiki_reverse_category_map($value)
      return $::__xowiki_reverse_category_map($value)
    } elseif {$map_type eq "party_id"} {
      return [:reverse_map_party  -entry $value  -default_party $creation_user  -create_user_ids $create_user_ids]
    } elseif {$value eq ""} {
      return ""
    } else {
      :msg "cannot map value '$value' (map_type $map_type) of ${:name} to an ID; maybe there is some same_named category tree with fewer entries..."
      :msg "reverse category map has values [lsort [array names ::__xowiki_reverse_category_map]]"
      return ""
    }
  }
::xowiki::FormPage instproc create_category_fields {} {
    set category_spec [:get_short_spec @categories]
    # Per default, no category fields in FormPages, since the can be
    # handled in more detail via form-fields.
    if {$category_spec eq ""} {return ""}

    # a value of "off" turns the off as well
    foreach f [split $category_spec ,] {
      if {$f eq "off"} {return ""}
    }

    set category_fields [list]
    set container_object_id ${:package_id}
    set category_trees [category_tree::get_mapped_trees $container_object_id]
    set category_ids [category::get_mapped_categories ${:item_id}]
    #:msg "mapped category ids=$category_ids"

    foreach category_tree $category_trees {
      lassign $category_tree tree_id tree_name subtree_id assign_single_p require_category_p

      set options [list]
      #if {!$require_category_p} {lappend options [list "--" ""]}
      set value [list]
      foreach category [::xowiki::Category get_category_infos  -subtree_id $subtree_id -tree_id $tree_id] {
        lassign $category category_id category_name deprecated_p level
        if {$category_id in $category_ids} {lappend value $category_id}
        set category_name [ns_quotehtml [lang::util::localize $category_name]]
        if { $level>1 } {
          set category_name "[string repeat {&nbsp;} [expr {2*$level-4}]]..$category_name"
        }
        lappend options [list $category_name $category_id]
      }
      set f [::xowiki::formfield::FormField new  -name "__category_${tree_name}_$tree_id"  -locale [:nls_language]  -label $tree_name  -type select  -value $value  -required $require_category_p]
      #:msg "category field ${:name} created, value '$value'"
      $f destroy_on_cleanup
      $f options $options
      $f multiple [expr {!$assign_single_p}]
      lappend category_fields $f
    }
    return $category_fields
  }
::xowiki::FormPage instproc group_assign {-group_id:integer,required -members:required {-rel_type membership_rel} {-member_state ""}} {
    set old_members [group::get_members -group_id $group_id]
    foreach m $members {
      if {$m ni $old_members} {
        #:msg "we have to add $m"
        group::add_member -group_id $group_id -user_id $m  -rel_type $rel_type -member_state $member_state
      }
    }
    foreach m $old_members {
      if {$m ni $members} {
        #:msg "we have to remove $m"
        group::remove_member -group_id $group_id -user_id $m
      }
    }
  }
::xowiki::FormPage instproc set_live_revision {-revision_id:required {-publish_status "ready"}} {
    next

    # Fetch fresh instance from db so that we have actual values
    # from the live revision for the update of the item_index.

    set page [::xo::db::CrClass get_instance_from_db -revision_id $revision_id]
    $page publish_status $publish_status
    $page update_item_index
  }
::xowiki::FormPage instproc initialize {} {
    # can be overloaded
  }
::xowiki::FormPage instproc marshall {{-mode export}} {
    #
    # Handle mapping from IDs to symbolic representations in
    # form-field values. We perform the mapping on xowiki::FormPages
    # and not on xowiki::Forms, since a single xowiki::FormPages might
    # use different xowiki::Forms in its life-cycle.
    #
    # Note that only types of form-fields implied by the derived form
    # constraints are recognized. E.g. In workflows, it might be
    # necessary to move e.g. category definitions into the global form
    # constraints.
    #
    if {$mode eq "copy" && ![string match "*revision_id*" ${:instance_attributes}]} {
      return [next]
    }
    set form_fields [:create_form_fields_from_form_constraints  [:get_form_constraints]]
    :build_instance_attribute_map $form_fields

    # In case we have a mapping from IDs to external values, use it
    # and rewrite instance attributes. Note that the marshalled
    # objects have to be flushed from memory later since the
    # representation of instances_attributes is changed by this
    # method.
    #
    if {[info exists :__instance_attribute_map]} {
      # :log "+++ we have an instance_attribute_map for ${:name}"
      # :log "+++ starting with instance_attributes [:instance_attributes]"
      array set multiple_index [list category 2 party_id 1 file 1]
      set ia [list]
      foreach {name value} [:instance_attributes] {
        #:log "marshall check $name $value [info exists use($name)]"
        if {[dict exists ${:__instance_attribute_map} $name]} {
          set use_name [dict get ${:__instance_attribute_map} $name]
          set map_type [lindex $use_name 0]
          set multiple [lindex $use_name $multiple_index($map_type)]
          #:log "+++ marshall check $name $value use <$use($name)> m=?$multiple"
          if {$multiple} {
            lappend ia $name [:map_values $map_type $value]
          } else {
            lappend ia $name [:map_value $map_type $value]
          }
        } else {
          # nothing to map
          lappend ia $name $value
        }
      }
      set :instance_attributes $ia
      #:log "+++ setting instance_attributes $ia"
    }
    set old_assignee [:assignee]
    set :assignee  [:map_party -property assignee $old_assignee]
    set r [next]
    set :assignee  $old_assignee
    return $r
  }
::xowiki::FormPage instproc compute_link_properties item_ref {
    set package_id ${:package_id}
    set page [::$package_id get_page_from_item_ref  -default_lang [:lang]  -parent_id ${:parent_id}  $item_ref]
    if {$page ne ""} {
      set item_id [$page item_id]
      set link_type [expr {[$page is_folder_page] ? "folder_link" : "link"}]
      set cross_package [expr {$package_id != [$page package_id]}]
    } else {
      set item_id 0
      set link_type "unresolved"
      set cross_package 0
    }
    #:msg [list item_ref $item_ref item_id $item_id link_type $link_type cross_package $cross_package]
    return [list item_ref $item_ref item_id $item_id link_type $link_type cross_package $cross_package]
  }
::xowiki::FormPage instproc include_header_info {{-prefix ""} {-js ""} {-css ""}} {
    if {$css eq ""} {set css [:get_from_template ${prefix}_css]}
    if {$js eq ""}  {set js [:get_from_template ${prefix}_js]}
    foreach line [split $js \n] {
      set line [string trim $line]
      if {$line ne ""} {
        ::xo::Page requireJS $line
      }
    }
    foreach line [split $css \n] {
      set line [string trim $line]
      if {$line eq ""} continue
      set order 1
      if {[llength $line]>1} {
        set e1 [lindex $line 0]
        if {[string is integer -strict $e1]} {
          set order $e1
          set line [lindex $line 1]
        }
      }
      ::xo::Page requireCSS -order $order $line
    }
  }
::xowiki::FormPage instproc update_langstring_property {attname lang} {
    :set_property $attname [:langstring $attname $lang [:property $attname]]
  }
::xowiki::FormPage instproc get_form_value att {
    #
    # Return the value contained in an HTML input field of the FORM
    # provided via the instance variable root.
    #
    set fields [${:root} selectNodes "//form//*\[@name='$att'\]"]
    if {$fields eq ""} {return ""}
    foreach field $fields {
      #
      # Handling first TEXTAREA
      #
      if {[$field nodeName] eq "textarea"} {
        return [$field nodeValue]
      }
      if {[$field nodeName] ne "input"} continue
      #
      # Handling now just INPUT types (only one needed so far)
      #
      set type [expr {[$field hasAttribute type] ? [$field getAttribute type] : "text"}]
      switch -- $type {
        checkbox {
          #:msg "get_form_value not implemented for $type"
        }
        radio {
          #:msg "get_form_value not implemented for $type"
        }
        hidden -
        password -
        text {
          if {[$field hasAttribute value]} {
            return [$field getAttribute value]
          }
        }
        default {
          #:log "can't handle $type so far $att=$value"
        }
      }
    }
    return ""
  }
::xowiki::FormPage instparametercmd mime_type
::xowiki::FormPage instparametercmd state
::xowiki::FormPage instparametercmd assignee
::xowiki::FormPage instparametercmd xowiki_form_page_id
::nsf::relation::set ::xowiki::FormPage superclass ::xowiki::PageInstance

::nx::slotObj -container slot ::xowiki::FormPage

::nsf::object::alloc ::xo::db::Attribute ::xowiki::FormPage::slot::xowiki_form_page_id {set :accessor public
   set :column_name xowiki_form_page_id
   set :configurable true
   set :convert false
   set :create_acs_attribute false
   set :create_table_attribute true
   set :datatype integer
   set :defaultmethods {}
   set :disposition alias
   set :domain ::xowiki::FormPage
   set :incremental false
   set :manager ::xowiki::FormPage::slot::xowiki_form_page_id
   set :max_n_values 1
   set :methodname xowiki_form_page_id
   set :min_n_values 1
   set :multiplicity 1..1
   set :name xowiki_form_page_id
   set :parameterSpec -xowiki_form_page_id
   set :per-object false
   set :position 0
   set :pretty_name ID
   set :pretty_plural {}
   set :references {}
   set :required false
   set :sqltype integer
   set :trace none
   : init}

::nsf::object::alloc ::xo::db::CrAttribute ::xowiki::FormPage::slot::assignee {set :accessor public
   set :column_name assignee
   set :configurable true
   set :convert false
   set :create_acs_attribute true
   set :create_table_attribute true
   set :datatype integer
   set :defaultmethods {}
   set :disposition alias
   set :domain ::xowiki::FormPage
   set :incremental false
   set :manager ::xowiki::FormPage::slot::assignee
   set :max_n_values 1
   set :methodname assignee
   set :min_n_values 1
   set :multiplicity 1..1
   set :name assignee
   set :parameterSpec -assignee
   set :per-object false
   set :position 0
   set :pretty_name #xowiki.FormPage-assignee#
   set :pretty_plural {}
   set :references parties(party_id)
   set :required false
   set :spec hidden
   set :sqltype integer
   set :trace none
   : init}

::nsf::object::alloc ::xotcl::Attribute ::xowiki::FormPage::slot::mime_type {set :accessor public
   set :configurable true
   set :convert false
   set :default text/plain
   set :defaultmethods {}
   set :disposition alias
   set :domain ::xowiki::FormPage
   set :incremental false
   set :manager ::xowiki::FormPage::slot::mime_type
   set :methodname mime_type
   set :multiplicity 1..1
   set :name mime_type
   set :parameterSpec {-mime_type:substdefault text/plain}
   set :per-object false
   set :position 0
   set :required false
   set :substdefault 0b111
   set :trace none
   : init}

::nsf::object::alloc ::xo::db::CrAttribute ::xowiki::FormPage::slot::state {set :accessor public
   set :column_name state
   set :configurable true
   set :convert false
   set :create_acs_attribute true
   set :create_table_attribute true
   set :datatype text
   set :default {}
   set :defaultmethods {}
   set :disposition alias
   set :domain ::xowiki::FormPage
   set :incremental false
   set :manager ::xowiki::FormPage::slot::state
   set :max_n_values 1
   set :methodname state
   set :min_n_values 1
   set :multiplicity 1..1
   set :name state
   set :parameterSpec {-state:substdefault {}}
   set :per-object false
   set :position 0
   set :pretty_name #xowiki.FormPage-state#
   set :pretty_plural {}
   set :references {}
   set :required false
   set :sqltype text
   set :substdefault 0b111
   set :trace none
   : init}

namespace eval ::xowiki {::namespace export Menu YUIMenuBar YUIMenuBarItem YUIMenu YUIMenuItem YUIMenuItemList YUIContextMenu YUIContextMenuItem}
XQL Not present:
Generic, PostgreSQL, Oracle
[ hide source ] | [ make this the default ]
Show another procedure: