1:- module(regex_state, [ adjust_case/3
    2                       , new_state/3
    3                       , push_capture/3
    4                       , singleline_mode/1
    5                       , numbered_captures/2
    6                       ]).    7:- use_module(library(apply), [ foldl/4 ]).    8:- use_module(library(assoc)).    9:- use_module(library(record)).   10
   11:- record state(i='-', s='-', capture_count=0, captures).
 new_state(+OptionSugar, +CaptureSugar, -State) is semidet
True if State is an opaque value representing the regular expression state described by OptionSugar and CapturesSugar. OptionSugar should be a list or an atom. If it's an atom it should be something like 'ims', 'xi', etc. Fails if OptionSugar contains an unknown option.
   20new_state(OptionSugar, CaptureSugar, State) :-
   21    atom(OptionSugar),
   22    OptionSugar \== [],  % empty list atom needs no expansion
   23    !,
   24    atom_chars(OptionSugar, Chars),
   25    new_state(Chars, CaptureSugar, State).
   26new_state(OptionList, CaptureSugar, State) :-
   27    var(CaptureSugar),
   28    !,
   29    new_state(OptionList, [], State).
   30new_state(OptionList, CaptureSugar, State) :-
   31    default_state(State0),
   32
   33    % set all options
   34    foldl(set_option, OptionList, State0, State1),
   35
   36    % prepare capture values
   37    empty_assoc(Captures),
   38    set_captures_of_state(Captures, State1, State2),
   39    foldl(push_pattern, CaptureSugar, State2, State3),
   40
   41    % next round of captures resumes numbering at the beginning
   42    set_capture_count_of_state(0, State3, State).
 set_option(+Option, +State0, -State) is semidet
Sets the option Option, giving a new State value.
   48set_option(i) -->
   49    set_i_of_state('+').
   50set_option(s) -->
   51    set_s_of_state('+').
 push_pattern(+Capture, +State0, -State) is semidet
Adds Capture to State0 giving a new State. Capture may be Name=Value or just Value
   58push_pattern(Capture, State0, State) :-
   59    var(Capture),
   60    !,
   61    push_numbered(Capture, State0, State).
   62push_pattern(Capture, State0, State) :-
   63    Capture = (Name=Value),
   64    !,
   65    ground(Name),
   66    push_named(Name, Value, State0, State).
   67push_pattern(Value, State0, State) :-
   68    % \+ var(Value)
   69    % \+ Value=(Name=_)
   70    push_numbered(Value, State0, State).
 push_capture(+Capture, +State0, -State) is semidet
Adds Capture to State0 giving a new State. Capture may be Name=Value or just Value. Pushing a named capture pushes both a named and a numbered capture.
   78push_capture(Capture, State0, State) :-
   79    var(Capture),
   80    !,
   81    push_numbered(Capture, State0, State).
   82push_capture(Capture, State0, State) :-
   83    Capture = (Name=Value),
   84    !,
   85    ground(Name),
   86    push_named(Name, Value, State0, State1),
   87    push_numbered(Value, State1, State).
   88push_capture(Value, State0, State) :-
   89    % \+ var(Value)
   90    % \+ Value=(Name=_)
   91    push_numbered(Value, State0, State).
 push_numbered(+Value, +State0, -State) is semidet
Add Value to State0 as a numbered capture producing a new State.
   97push_numbered(Value, State0, State) :-
   98    % retrieve current values
   99    state_capture_count(State0, Count0),
  100    state_captures(State0, Captures0),
  101
  102    % create new values
  103    insert_pair(Count0, Value, Captures0, Captures1),
  104    succ(Count0, Count),
  105
  106    % bundle them into a new state value
  107    set_capture_count_of_state(Count, State0, State1),
  108    set_captures_of_state(Captures1, State1, State).
 push_named(+Name, +Value, +State0, -State) is semidet
Add Name and Value pair to State0 producing a new State.
  114push_named(Name, Value, State0, State) :-
  115    % retrieve current values
  116    state_captures(State0, Captures0),
  117
  118    % create new value
  119    insert_pair(Name, Value, Captures0, Captures),
  120
  121    % bundle into a new state value
  122    set_captures_of_state(Captures, State0, State).
  123
  124
  125% unify a value with a named value; create a named value if the name
  126% doesn't yet exist
  127insert_pair(Name, Value, Assoc, Assoc) :-
  128    get_assoc(Name, Assoc, CurrentValue),
  129    !,
  130    Value = CurrentValue.
  131insert_pair(Name, Value, Assoc0, Assoc) :-
  132    put_assoc(Name, Assoc0, Value, Assoc).
 numbered_captures(+State, -Captures:list) is det
True if Captures is a list of numbered captures in State.
  138numbered_captures(State, List) :-
  139    state_capture_count(State, N),
  140    state_captures(State, Captures),
  141    numbered_captures(0, N, Captures, List).
  142numbered_captures(N, N, _, []) :-
  143    !.
  144numbered_captures(N0, N, Captures, [Value|Tail]) :-
  145    get_assoc(N0,Captures,Value),
  146    succ(N0, N1),
  147    numbered_captures(N1,N,Captures,Tail).
 adjust_case(+Options, +Code0, -Code) is det
True if Code represents the same letter as Code0 but with case adjusted to compensate for the 'i' regular expression option (aka case insensitive).
  155adjust_case(Options, Code0, Code) :-
  156    ( state_i(Options, '+') ->
  157          code_type(Code, to_lower(Code0))
  158    ; % otherwise ->
  159          Code = Code0
  160    ).
 singleline_mode(+Options) is semidet
True if Options request single-line mode (`/s`).
  165singleline_mode(Options) :-
  166    state_s(Options, '+')