miniroon

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

spec.pl (3290B)


      1 :- use_module(library(error)).
      2 :- use_module(library(dcg/basics)).
      3 
      4 :- op(950, xfx, will_be).
      5 
      6 %%% Basic definitions
      7 
      8 % swapped arguments append for use in DCGs
      9 % when called with instanced list as first argument it unifies it's content with DCG.
     10 dcgappend([], L, L) :- !.
     11 dcgappend([H|T], [H|R], L) :-
     12     dcgappend(T, R, L).
     13 %dcgappend(List, L0, L1) :- append(List, L1, L0).
     14 
     15 % apply check to value when bound
     16 will_be(Value, Goal) :-
     17 	freeze(Value, assertion(call(Goal, Value))).
     18 
     19 byte(Value) :- must_be(between(0, 255), Value).
     20 
     21 nonnegative_integer(Value) :- must_be(nonneg, Value).
     22 
     23 sequence_of_bytes([]).
     24 sequence_of_bytes([First|Rest]) :-
     25 	First will_be byte,
     26 	Rest will_be sequence_of_bytes.
     27 
     28 netstring_encoding(PayloadBytes) -->  %> Netstring is a sequence of bytes.
     29 	netstring_prefix_for_payload(PayloadBytes),  %> It consists of prefix,
     30 	PayloadBytes, %> payload,
     31 	`,`.  %> and terminator. Terminator is single ASCII comma `,`.
     32 netstring_encoding(netstring(PayloadBytes), Bytes) :-
     33 	assertion(ground(PayloadBytes); ground(Bytes)),
     34 	Bytes will_be sequence_of_bytes,
     35 	phrase(netstring_encoding(PayloadBytes), Bytes).
     36 
     37 %> Netstring prefix is the shortest ASCII decimal representation for length of
     38 %^ payload in bytes, followed by ASCII colon `:`.
     39 %^ That is number starting with non-zero digit unless payload is empty,
     40 %^ in which case it's `0`.
     41 netstring_prefix_for_payload(PayloadBytes, A, B) :-
     42 	(  var(PayloadBytes)
     43 	-> netstring_prefix_codes(Prefix, A, B),
     44 	   number_codes(PayloadLength, Prefix),
     45 	   length(PayloadBytes, PayloadLength)
     46 	;  length(PayloadBytes, PayloadLength),
     47 	   number_codes(PayloadLength, Prefix),
     48 	   netstring_prefix_codes(Prefix, A, B)
     49 	).
     50 netstring_prefix_codes(`0`) --> `0:`, !.
     51 netstring_prefix_codes([C|Cs]) -->
     52 	nonzero_digit(C),
     53 	!,
     54 	digits(Cs),
     55 	`:`.
     56 
     57 nonzero_digit(Code) -->
     58 	[Code],
     59 	{ assertion(ground(Code)) },
     60 	{ member(Code, `123456789`) }.
     61 
     62 netstring_of(Goal, Bytes) :-
     63 	ground(Goal),
     64 	!,
     65 	call(Goal, PayloadBytes),
     66 	netstring_encoding(netstring(PayloadBytes), Bytes).
     67 
     68 netstring_of(Goal, Bytes) :-
     69 	ground(Bytes),
     70 	!,
     71 	netstring_encoding(netstring(PayloadBytes), Bytes),
     72 	call(Goal, PayloadBytes).
     73 
     74 % Miniroon is a netstring whose payload is concatenation of three parts: header, caveat list and signature.
     75 
     76 %miniroon_encoding(header_capv0(Identifier, Action), Caveats, Signature, Bytes) :-
     77 %	assertion(false). % TODO
     78 
     79 phrase_length_agg(List, Terminator, CurrentDepth, Length) :-
     80 	(  List == Terminator
     81 	-> CurrentDepth = Length
     82 	;  NextDepth is CurrentDepth + 1,
     83 	   assertion(compound(List)),
     84 	   List = [_|NextList],
     85 	   phrase_length_agg(NextList, Terminator, NextDepth, Length)
     86 	).
     87 
     88 phrase_length(DCGBody, List, Rest, Length) :-
     89 	phrase(DCGBody, List, Terminator),
     90 	phrase_length_agg(List, Terminator, 0, Length),
     91 	Terminator = Rest.
     92 
     93 nsdcg(DCGBody, L0, Rest) :-
     94 	var(L0),
     95 	!,
     96 	phrase_length(DCGBody,Payload,[44|Rest],PayloadLength),
     97 	number_codes(PayloadLength, PrefixDigits),
     98 	netstring_prefix_codes(PrefixDigits, L0, Payload).
     99 
    100 nsdcg(DCGBody, L0, Rest) :-
    101 	assertion(nonvar(L0)),
    102 	netstring_prefix_codes(PrefixDigits, L0, Payload),
    103 	number_codes(PayloadLength, PrefixDigits),
    104 	phrase_length(DCGBody,Payload,[44|Rest],PayloadLength).
    105 
    106 % :- use_module(library(pldoc/doc_files)).
    107 % doc_save('spec.pl', [format(html), doc_root(.)]).