Files
eopenid/ehtml-fix.patch

55 lines
1.7 KiB
Diff

Fix EHTML parser
From: Gregory Haskins <ghaskins@novell.com>
The current code assumes {X1, X2, X3} when is_list(X3), which is not always the case.
Running a v1 discovery against ssocircle.com returns the following:
<html><head>
<link rel="openid.server" href="http://idp.ssocircle.com/sso/idservice">
</head><body>
(note the single <link> element)
This results in an EHTML of the form {_, _, {link, ...} which crashes the code when we try
to apply {link, ..} as a parameter to lists:foldl(). This adds code to handle the non-list
types.
Signed-off-by: Gregory Haskins <ghaskins@novell.com>
---
src/eopenid_v1.erl | 18 +++++++++++-------
1 files changed, 11 insertions(+), 7 deletions(-)
diff --git a/src/eopenid_v1.erl b/src/eopenid_v1.erl
index 629eb73..c50ab9b 100644
--- a/src/eopenid_v1.erl
+++ b/src/eopenid_v1.erl
@@ -317,13 +317,17 @@ pick(S, _, _) -> S.
gelems(Path, Tree) ->
ordsets:to_list(gelems(Path, [Tree], ordsets:new())).
-gelems([E], L, S) ->
- lists:foldl(fun({X,_,_}=N, Acc) when X == E ->
- ordsets:add_element(N,Acc);
- ({X,_}=N, Acc) when X == E ->
- ordsets:add_element(N,Acc);
- (_, Acc) -> Acc
- end, S, L);
+gelem_add(E, {X,_,_}=N, Acc) when X == E ->
+ ordsets:add_element(N,Acc);
+gelem_add(E, {X,_}=N, Acc) when X == E ->
+ ordsets:add_element(N,Acc);
+gelem_add(E, _, Acc) -> Acc.
+
+gelems([E], L, S) when is_list(L) ->
+ F = fun(N, Acc) -> gelem_add(E, N, Acc) end,
+ lists:foldl(F, S, L);
+gelems([E], I, S) ->
+ gelem_add(E, I, S);
gelems([E|T], L, S) when is_list(L) ->
lists:foldl(fun({X,_,Xl}, Acc) when X == E ->
gelems(T, Xl, Acc);