miniroon

Simplistic macaroon-based authorization for Unix systems
git clone https://ccx.te2000.cz/git/miniroon
Log | Files | Refs | README

tests.pl (8235B)


      1 :- use_module(library(debug), [assertion/1]).
      2 :- use_module(library(yall)).
      3 
      4 :- use_module(miniroon_spec).
      5 
      6 test_one_result(Template, Goal, Output) :-
      7 	findall(Template, Goal, Results),
      8 	assertion(length(Results, 1)),
      9 	Results = [Output].
     10 
     11 test_result_matches(Template, Goal, Expected) :-
     12 	test_one_result(Template, Goal, Output),
     13 	assertion(Output =@= Expected).
     14 
     15 test_decode_dcg(Bytes, Template, Goal, Expected) :-
     16 	test_result_matches(Template, phrase(Goal, Bytes), Expected).
     17 
     18 test_encode(Goal, ExpectedBytes) :-
     19 	test_one_result(Bytes, call(Goal, Bytes), OutputBytes),
     20 	string_bytes(Output, OutputBytes, octet),
     21 	string_bytes(Expected, ExpectedBytes, octet),
     22 	assertion(Output =@= Expected).
     23 
     24 test_encode_dcg(Goal, ExpectedBytes) :-
     25 	test_one_result(Bytes, phrase(Goal, Bytes), OutputBytes),
     26 	string_bytes(Output, OutputBytes, octet),
     27 	string_bytes(Expected, ExpectedBytes, octet),
     28 	assertion(Output =@= Expected).
     29 
     30 :- begin_tests(spec_helpers).
     31 
     32 test(dcgappend1) :-
     33 	phrase_length(``, Bytes, [], Length),
     34 	assertion(Bytes =@= ``),
     35 	assertion(Length =@= 0).
     36 
     37 test(dcgappend2) :-
     38 	phrase_length(`abcd`, Bytes, [], Length),
     39 	assertion(Bytes =@= `abcd`),
     40 	assertion(Length =@= 4).
     41 
     42 test(dcgappend3) :-
     43 	phrase_length(`abcd`, Bytes, Next, Length1),
     44 	phrase_length(`efgh`, Next, [], Length2),
     45 	assertion(Bytes =@= `abcdefgh`),
     46 	assertion(Length1 =@= 4),
     47 	assertion(Length2 =@= 4).
     48 
     49 test(dcgappend4) :-
     50 	phrase_length(`efgh`, Next, [], Length2),
     51 	phrase_length(`abcd`, Bytes, Next, Length1),
     52 	assertion(Bytes =@= `abcdefgh`),
     53 	assertion(Length1 =@= 4),
     54 	assertion(Length2 =@= 4).
     55 
     56 test(dcgappend5) :-
     57 	Bytes = `abcdefgh`,
     58 	phrase_length(`abcd`, Bytes, Next, Length1),
     59 	assertion(Next =@= `efgh`),
     60 	assertion(Length1 =@= 4).
     61 
     62 :- end_tests(spec_helpers).
     63 
     64 :- begin_tests(spec_netstring).
     65 
     66 test(prefix_encode_empty) :-
     67 	PayloadBytes = ``,
     68 	phrase(netstring_prefix_for_payload(PayloadBytes), PrefixBytes),
     69 	assertion(PrefixBytes =@= `0:`).
     70 
     71 test(prefix_decode_empty) :-
     72 	PrefixBytes = `0:`,
     73 	phrase(netstring_prefix_for_payload(PayloadBytes), PrefixBytes),
     74 	assertion(PayloadBytes =@= ``).
     75 
     76 values_netstring_bytes(empty, ``, `0:,`, `3:0:,,`).
     77 values_netstring_bytes(single_null, `\0`, `1:\0,`, `4:1:\0,,`).
     78 values_netstring_bytes(min_max, [0, 255], Bytes, Twice) :-
     79 	flatten([`2:\0`, 255, `,`], Bytes),
     80 	flatten([`5:`, Bytes, `,`], Twice).
     81 values_netstring_bytes(ten_bytes, `1234567890`, `10:1234567890,`, `14:10:1234567890,,`).
     82 
     83 test(netstring_bytes_encode, [
     84 	forall(values_netstring_bytes(_Name, PayloadBytes, Bytes, _))
     85 ]) :-
     86 	test_encode_dcg(netstring_bytes(PayloadBytes), Bytes).
     87 
     88 test(netstring_bytes_decode_variant, [
     89 	forall(values_netstring_bytes(_Name, PayloadBytes, Bytes, _))
     90 ]) :-
     91 	test_decode_dcg(Bytes, Result, netstring_bytes(Result), PayloadBytes).
     92 
     93 test(netstring_bytes_decode, [
     94 	forall(values_netstring_bytes(_Name, PayloadBytes, Bytes, _))
     95 ]) :-
     96 	test_result_matches(Result, phrase(netstring_bytes(Result), Bytes), PayloadBytes).
     97 
     98 test(netstring_bytes_nested_encode, [
     99 	forall(values_netstring_bytes(_Name, PayloadBytes, _, Bytes))
    100 ]) :-
    101 	test_encode_dcg(netstring_call_dcg(netstring_bytes(PayloadBytes)), Bytes).
    102 
    103 test(netstring_bytes_nested_decode, [
    104 	forall(values_netstring_bytes(_Name, PayloadBytes, _, Bytes))
    105 ]) :-
    106 	test_result_matches(
    107 		Result,
    108 		phrase(netstring_call_dcg(netstring_bytes(Result)), Bytes),
    109 		PayloadBytes
    110 	).
    111 
    112 test(encode_netstring_call_dcg) :-
    113 	InnerPayload = [0, 255],
    114 	flatten([`5:2:\0`, 255, `,,`], ExpectedBytes),
    115 	phrase_length(netstring_call_dcg(netstring_call_dcg(dcgappend(InnerPayload))), Bytes, [], Length),
    116 	assertion(Bytes =@= ExpectedBytes),
    117 	assertion(Length =@= 8).
    118 
    119 test(decode_netstring_call_dcg) :-
    120 	ExpectedPayload = [0, 255],
    121 	flatten([`5:2:\0`, 255, `,,`], Bytes),
    122 	InnerPayload = [_,_],
    123 	phrase_length(netstring_call_dcg(netstring_call_dcg(dcgappend(InnerPayload))), Bytes, [], Length),
    124 	assertion(InnerPayload =@= ExpectedPayload),
    125 	assertion(Length =@= 8).
    126 
    127 test(decode_netstring_call_dcg_single) :-
    128 	ExpectedPayload = [0, 255],
    129 	flatten([`2:\0`, 255, `,`], Bytes),
    130 	InnerPayload = [_,_],
    131 	phrase_length(netstring_call_dcg(dcgappend(InnerPayload)), Bytes, [], Length),
    132 	assertion(InnerPayload =@= ExpectedPayload),
    133 	assertion(Length =@= 5).
    134 
    135 % TODO: netstring_maplist_dcg
    136 
    137 :- end_tests(spec_netstring).
    138 
    139 :- begin_tests(spec_miniroon).
    140 
    141 test(header_v0_decode) :-
    142 	ExpectedHeader = header_v0(`example1`, invoke),
    143 	Bytes = `28:5:capv0,8:example1,6:invoke,,`,
    144 	test_result_matches(
    145 		Header, 
    146 		phrase(netstring_call_dcg(miniroon_header(Header)), Bytes),
    147 		ExpectedHeader
    148 	).
    149 
    150 test(header_v0_encode) :-
    151 	Header = header_v0(`example1`, invoke),
    152 	ExpectedBytes = `28:5:capv0,8:example1,6:invoke,,`,
    153 	test_encode_dcg(netstring_call_dcg(miniroon_header(Header)), ExpectedBytes).
    154 
    155 test(caveat_list_v0_decode_empty) :-
    156 	ExpectedCaveats = [],
    157 	Bytes = `0:,`,
    158 	findall(Caveats, phrase(netstring_call_dcg(miniroon_v0_caveat_list(Caveats)), Bytes), Results),
    159 	Results = [OutputCaveats],
    160 	assertion(OutputCaveats =@= ExpectedCaveats).
    161 
    162 test(caveat_list_v0_encode_empty) :-
    163 	Caveats = [],
    164 	ExpectedBytes = `0:,`,
    165 	test_encode_dcg(netstring_call_dcg(miniroon_v0_caveat_list(Caveats)), ExpectedBytes).
    166 
    167 test(caveat_list_v0_encode_one) :-
    168 	Caveats = [caveat_v0_env_absent("var2")],
    169 	ExpectedBytes = `25:21:10:env-absent,4:var2,,,`,
    170 	test_encode_dcg(netstring_call_dcg(miniroon_v0_caveat_list(Caveats)), ExpectedBytes).
    171 
    172 test(caveat_list_v0_decode_one) :-
    173 	ExpectedCaveats = [caveat_v0_env_absent("var2")],
    174 	Bytes = `25:21:10:env-absent,4:var2,,,`,
    175 	findall(Caveats, phrase(netstring_call_dcg(miniroon_v0_caveat_list(Caveats)), Bytes), Results),
    176 	Results = [OutputCaveats],
    177 	assertion(OutputCaveats =@= ExpectedCaveats).
    178 
    179 test(caveat_list_v0_decode) :-
    180 	ExpectedCaveats = [
    181 		caveat_v0_env_is("var1", "hello"),
    182 		caveat_v0_env_absent("var2"),
    183 		caveat_v0_env_glob("var3", "_*"),
    184 		caveat_v0_env_is("var3", "_hello")
    185 	],
    186 	Bytes = `109:24:6:env-is,4:var1,5:hello,,21:10:env-absent,4:var2,,23:8:env-glob,4:var3,2:_*,,25:6:env-is,4:var3,6:_hello,,,`,
    187 	test_result_matches(
    188 		Caveats,
    189 		phrase(netstring_call_dcg(miniroon_v0_caveat_list(Caveats)), Bytes),
    190 		ExpectedCaveats
    191 	).
    192 
    193 test(caveat_list_v0_encode) :-
    194 	Caveats = [
    195 		caveat_v0_env_is("var1", "hello"),
    196 		caveat_v0_env_absent("var2"),
    197 		caveat_v0_env_glob("var3", "_*"),
    198 		caveat_v0_env_is("var3", "_hello")
    199 	],
    200 	ExpectedBytes = `109:24:6:env-is,4:var1,5:hello,,21:10:env-absent,4:var2,,23:8:env-glob,4:var3,2:_*,,25:6:env-is,4:var3,6:_hello,,,`,
    201 	test_encode_dcg(netstring_call_dcg(miniroon_v0_caveat_list(Caveats)), ExpectedBytes).
    202 
    203 test(decode_example1) :-
    204 	ExpectedSignature = [
    205 		0xda, 0xde, 0xbd, 0xd0, 0xf3, 0x39, 0x14, 0x7c,
    206 		0xbe, 0x48, 0xaa, 0x0c, 0x5d, 0x1f, 0xa4, 0xff,
    207 		0x87, 0x58, 0x65, 0x79, 0xff, 0x89, 0x28, 0xb5,
    208 		0xda, 0xb3, 0x4e, 0x7c, 0x5d, 0xfa, 0x4a, 0x89
    209 	],
    210 	ExpectedCaveats = [
    211 		caveat_v0_env_is("var1", "hello"),
    212 		caveat_v0_env_absent("var2"),
    213 		caveat_v0_env_glob("var3", "_*"),
    214 		caveat_v0_env_is("var3", "_hello")
    215 	],
    216 	flatten([
    217 		`182:`,
    218 		`28:5:capv0,8:example1,6:invoke,,`,
    219 		`109:24:6:env-is,4:var1,5:hello,,21:10:env-absent,4:var2,,23:8:env-glob,4:var3,2:_*,,25:6:env-is,4:var3,6:_hello,,,`,
    220 		`32:`,
    221 		ExpectedSignature,
    222 		`,,`
    223 	], Bytes),
    224 	ExpectedMiniroon = miniroon_v0(`example1`, invoke, ExpectedCaveats, ExpectedSignature),
    225 	assertion(ground(Bytes)),
    226 	assertion(ground(ExpectedMiniroon)),
    227 	test_result_matches(Miniroon, miniroon_encoding(Miniroon, Bytes), ExpectedMiniroon).
    228 
    229 test(encode_example1) :-
    230 	Signature = [
    231 		0xda, 0xde, 0xbd, 0xd0, 0xf3, 0x39, 0x14, 0x7c,
    232 		0xbe, 0x48, 0xaa, 0x0c, 0x5d, 0x1f, 0xa4, 0xff,
    233 		0x87, 0x58, 0x65, 0x79, 0xff, 0x89, 0x28, 0xb5,
    234 		0xda, 0xb3, 0x4e, 0x7c, 0x5d, 0xfa, 0x4a, 0x89
    235 	],
    236 	Caveats = [
    237 		caveat_v0_env_is("var1", "hello"),
    238 		caveat_v0_env_absent("var2"),
    239 		caveat_v0_env_glob("var3", "_*"),
    240 		caveat_v0_env_is("var3", "_hello")
    241 	],
    242 	flatten([
    243 		`182:`,
    244 		`28:5:capv0,8:example1,6:invoke,,`,
    245 		`109:24:6:env-is,4:var1,5:hello,,21:10:env-absent,4:var2,,23:8:env-glob,4:var3,2:_*,,25:6:env-is,4:var3,6:_hello,,,`,
    246 		`32:`,
    247 		Signature,
    248 		`,,`
    249 	], ExpectedBytes),
    250 	Miniroon = miniroon_v0(`example1`, invoke, Caveats, Signature),
    251 	assertion(ground(Miniroon)),
    252 	test_encode(miniroon_encoding(Miniroon), ExpectedBytes).
    253 
    254 :- end_tests(spec_miniroon).