This file is indexed.

/usr/share/Yap/clpbn/hmm.yap is in yap 5.1.3-6.

This file is owned by root:root, with mode 0o644.

The actual contents of the file can be viewed below.

 1
 2
 3
 4
 5
 6
 7
 8
 9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
:- module(hmm, [init_hmm/0,
		  hmm_state/1,
		  emission/1]).

:- ensure_loaded(library(clpbn)).

:- use_module(library(lists),
	      [nth/3]).

:- use_module(library(nbhash),
	      [nb_hash_new/2,
	       nb_hash_lookup/3,
	       nb_hash_insert/3
	      ]).

:- ensure_loaded(library(tries)).

:- meta_predicate hmm_state(:).

:- dynamic hmm_tabled/1.

:- attribute emission/1.

:- ensure_loaded(library('clpbn/viterbi')).

init_hmm :-
%	retractall(hmm_tabled(_)).
%	eraseall(hmm_tabled).
%	nb_hash_new(hmm_table, 1000000).
	trie_open(Trie), nb_setval(trie,Trie).

hmm_state(Mod:A) :- !, hmm_state(A,Mod).
hmm_state(A) :- prolog_flag(typein_module,Mod), hmm_state(A,Mod).

hmm_state(Mod:N/A,_) :- !,
	hmm_state(N/A,Mod).
hmm_state((A,B),Mod) :- !,
	hmm_state(A,Mod),
	hmm_state(B,Mod).
hmm_state(N/A,Mod) :-
	atom_codes(N,[TC|_]),
	atom_codes(T,[TC]),
	build_args(A,LArgs,KArgs,First,Last),
	Key =.. [T|KArgs],
	Head =.. [N|LArgs],
	asserta_static( (Mod:Head :-
	        ( First > 2 -> 
		  Last = Key, !
		;
%		  hmm:hmm_tabled(Key)
%		  nb_hash:nb_hash_lookup(hmm_table, Key, [])
		  nb_getval(trie, Trie), trie_check_entry(Trie, Key, _)
		->
		  % leave work for solver!
		  %
		  Last = Key, !
		;
		  % first time we saw this entry
%		  assert(hmm:hmm_tabled(Key)),
%		  nb_hash:nb_hash_insert(hmm_table,Key,[]),
		  nb_getval(trie, Trie), trie_put_entry(Trie, Key, _),
		  fail
		)
	      )
	      ).
	
build_args(4,[A,B,C,D],[A,B,C],A,D).
build_args(3,  [A,B,C],  [A,B],A,C).
build_args(2,    [A,B],    [A],A,B).

emission(V) :-
	put_atts(V,[emission(Prob)]).

cvt_vals(aminoacids,[a,  c,  d,  e,  f,  g,  h,  i,  k,  l,  m,  n,  p,  q,  r,  s,  t,  v,  w,  y]).
cvt_vals(bool,[t,f]).
cvt_vals(dna,[a,c,g,t]).
cvt_vals(rna,[a,c,g,u]).
cvt_vals([A|B],[A|B]).

% first, try standard representation
find_probs(Logs,Nth,Log) :-
	arg(Nth,Logs,Log).