8:- use_module(library(mcintyre)). 9
10:- if(current_predicate(use_rendering/1)). 11:- use_rendering(c3). 12:- use_rendering(graphviz). 13:- endif. 14
15:- mc. 16
17:- begin_lpad. 18
23
24hmm(O):-hmm(_,O).
27
28hmm(S,O):-trans(start,Q0,[]),hmm(Q0,[],S0,O),reverse(S0,S).
31
32hmm(Q,S0,S,[L|O]):-
33 trans(Q,Q1,S0),
34 out(L,Q,S0),
35 hmm(Q1,[Q|S0],S,O).
38
39hmm(_,S,S,[]).
41
42
43trans(start,det,_):0.30;
44trans(start,aux,_):0.20;
45trans(start,v,_):0.10;
46trans(start,n,_):0.10;
47trans(start,pron,_):0.30.
48
49trans(det,det,_):0.20;
50trans(det,aux,_):0.01;
51trans(det,v,_):0.01;
52trans(det,n,_):0.77;
53trans(det,pron,_):0.01.
54
55trans(aux,det,_):0.18;
56trans(aux,aux,_):0.10;
57trans(aux,v,_):0.50;
58trans(aux,n,_):0.01;
59trans(aux,pron,_):0.21.
60
61trans(v,det,_):0.36;
62trans(v,aux,_):0.01;
63trans(v,v,_):0.01;
64trans(v,n,_):0.26;
65trans(v,pron,_):0.36.
66
67trans(n,det,_):0.01;
68trans(n,aux,_):0.25;
69trans(n,v,_):0.39;
70trans(n,n,_):0.34;
71trans(n,pron,_):0.01.
72
73trans(pron,det,_):0.01;
74trans(pron,aux,_):0.45;
75trans(pron,v,_):0.52;
76trans(pron,n,_):0.01;
77trans(pron,pron,_):0.01.
78
86out(a,det,_).
87out(can,aux,_).
88out(can,v,_).
89out(can,n,_).
90out(he,pron,_).
91
92
93:- end_lpad. 94
95state_diagram(digraph(G)):-
96 setof(A,(B,S,Body)^
97 clause(trans(A,B,S),Body),Nodes),
98 maplist(nodelab,Nodes,NodesLab),
99 findall(edge(A -> B,[label=P]),
100 (clause(trans(A,B,_),
101 sample_head(_,_,_,Probs,N)),
102 nth0(N,Probs,_:P)),
103 Edges),
104 append(NodesLab,Edges,G).
105
106nodelab(N,node(N,[label=Lab])):-
107 findall(W,clause(out(W,N,_),_),L),
108 atomic_list_concat([N,'\nOut:\n'|L],Lab).
?-
mc_sample_arg(hmm(S,[he,can,can,a,can]),20,S,O)
. % sample the state sequence corresonding to the phrase "he can can a can" % the most frequent state sequence is an approximate POS tagging for the % sentence. It corresponds to the Viterbi path of the HMM. % expected result: the most frequent tagging should be [pron, aux, v, det, n] ?-mc_sample_arg(hmm(S,[he,can,can,a,can]),20,S,O)
,argbar(O,C)
.?-
state_diagram(G)
. % show the state diagram */