Did you know ... Search Documentation:
Pack ccprism -- prolog/ccprism/graph.pl
PublicShow source

This module provides algorithms on explanation hypergraphs, based on the ideas of Sato (in PRISM), Klein and Manning [1] and Goodman [2]. Also provided are methods for sampling explanations from their posterior distribution [2] and computing the entropy of the posterior distribution using a method which, to my knowledge, has not been published before.

[1] D. Klein and C. D. Manning. Parsing and hypergraphs. In New developments in parsing technology, pages 351–372. Springer, 2004.

[2] J. Goodman. Parsing inside-out. PhD thesis, Division of Engineering and Applied Sciences, Harvard University, 1998.

tree ---> goal - list(tree).
igraph == f_graph(pair,float,float,float)
       == list(pair(goal,weighted(list(weighted(list(weighted(factor)))))))
weighted(X) == pair(float,X).
 top_value(+Pairs:list(pair(goal,A)), -X:A) is semidet
Extract the value associated with the goal '^top':top from a list of goal-value pairs. This can be applied to explanation graphs or the results of graph_fold/4.
 prune_graph(+P:pred(+tcall(F,_,D),-D), +Top:goal, +G1:f_graph(F,A,B,C), -G2:f_graph(F,A,B,C)) is det
f_graph(F,A,B,C) == list(pair(goal,tcall(F,A,list(tcall(F,B,list(tcall(F,C,factor)))))))

Prune a graph or annotated graph to keep only goals reachable from a given top goal. With apologies, the type is quite complicated. The input and output graphs are lists of goals paired with annotated explanations. The type of an annotation is described by the type constructor F: F(E,D) is the type of a D annotated with an E. The first argument P knows how to strip off any type of annotation and return the D. This is how we dig down into the annotated explanations to find out which subgoals are referenced. For example, if F = pair, then P should be snd. If F(E,D) = D (ie no annotation), then P should be (=). Since PlDoc won't accept high-order type terms, we write F(E,D) as tcall(F,E,D), where tcall is like call for types.

 graph_switches(+G:graph, -SWs:list(switch(_))) is det
Extract list of switches referenced in an explanation graph.
 graph_fold(+SR:sr(A,B,C,T), ?P:params(T), +G:graph, -R:list(pair(goal,W))) is det
Folds the semiring SR over the explanation graph G. Produces R, a list of pairs of goals in the original graph with the result of the fold for that goal. Different semirings can produce many kinds of parsing analysis. The algebra is not strictly a semiring, as the times and plus operators have types A, B -> B and B, C -> C respectively as this makes it easier to avoid unnecessary operations like list appending.

An algebra of type sr(A,B,C,T) must provide 4 operators and 2 values:

inject  : T, factor -> A
times   : A, B -> B
plus    : B, C -> C
project : goal, C -> A, W
unit    : B
zero    : C

Semirings are extensible using multifile predicates sr_inj/4, sr_proj/5, sr_times/4, sr_plus/4, sr_unit/2 and sr_zero/2.

Available semirings in this module:

r(pred(+T,-A),pred(+C,-C),pred(+A,+B,-B),pred(+B,+C,-C))
A term containing the operators in restricted forms as callable terms. The unit and zero for the times and plus operators respectively are looked up in m_zero/2.
best
Finds the best single explanation for each goal. Parameters are assumed to be probabilities.
ann(sr(A,B,C,T))
Annotates the original hypergraph with the results of any semiring analysis.
sr(A1,B1,C1,T)-sr(A1,B1,C1,T)
For each goal, return a pair of results from any two semiring analyses.

Various standard analysis can be obtained by using the appropriate semiring:

r(=,=,mul,add)
Inside algorithm from linear probabilities.
r(=,lse,add,cons)
Inside algorithm with log-scaling from log probabilities
r(=,=,mul,max)
Viterbi probabilities.
 graph_inside(+G:graph, ?P:sw_params, -IG:igraph) is det
 igraph_sample_tree(+IG:igraph, +H:goal, -Ts:list(tree)) is det
Uses prob effect to sample a tree from a graph annotated with inside probabilities, as produced by graph_inside/3/
 igraph_entropy(+S:scaling, +IG:igraph, -Es:list(pair(goal,float))) is det
Explanation entropies from annotated explanation graph.
 graph_counts(+Meth:counts_method, +PSc:scaling, +G:graph, P:sw_params, C:sw_params, LP:float) is det
Compute expected switch counts C from explanation graph G with switch parameters P. Uses automatic differentiation of the expression for the log of the inside probability LP of the graph. Params can be unbound - binding them later triggers the computations required to yield numerical values in the result.
counts_method ---> io(scaling); vit.
 accum_stats(+Acc:pred(fmap(int),fmap(int)), +GSWs:pred(fmap(int),list(switch(_))), -Stats:sw_params) is det
 tree_stats(+T:tree, -C:sw_params) is det

Undocumented predicates

The following predicates are exported, but not or incorrectly documented.

 top_goal(Arg1)
 sw_trees_stats(Arg1, Arg2, Arg3)