1%-----------------------------------------------------------------------------%
    2% vim: ft=prolog ts=4 sw=4 et wm=0 tw=0
    3%-----------------------------------------------------------------------------%
    4:-module(destruction, [ ':='/2,   op(700, xfx, :=),
    5                        ':=:'/2,  op(700, xfx, :=:),
    6                        iss/2,    op(700, xfx, iss),
    7                        '++'/1,   op(500, xf,  ++),
    8                        '--'/1,   op(500, xf,  --),
    9                        '+:+'/1,  op(500, xf,  +:+),
   10                        '-:-'/1,  op(500, xf,  -:-),
   11                        '++'/1,   op(500, fx,  ++),
   12                        '--'/1,   op(500, fx,  --),
   13                        '+:+'/1,  op(500, fx,  +:+),
   14                        '-:-'/1,  op(500, fx,  -:-),
   15                        defvar/1, op(400, fx,  defvar)  ]).

Destructive variables (d-variables)

* Aren't we all bored of NN is N+1? Why go through all this hassle? Good news everyone: this module allows you to release your inner god of chaos and use destructive assignment - in PROLOG!

Of course, everything comes with a price; if you thought that =/2 vs ==/2 vs =':='/2 vs is/2 is confusing then you might want to run...

author
- Thanos Tintinidis <thanosqr@gmail.com>
version
- 1.0
See also
- http://en.wikipedia.org/wiki/Alignment_%28Dungeons_%26_Dragons%29#Chaotic_Evil
deprecated
-
license
- This program is free software. It comes without any warranty, to the extent permitted by applicable law. You can redistribute it and/or modify it under the terms of the Do What The Fuck You Want To Public License, Version 2, as published by Sam Hocevar. See the file COPYING in the project root directory or consult http://www.wtfpl.net/txt/copying for more details.
To be done
-
Destructive assignments can never stop; therefore, this module is eternally in a state of flux /
   42:- multifile license:license/3.   43licence:license(wtfpl, lgpl,
   44                [ comment('Do What The Fuck You Want To Public License'),
   45                  url('http://www.wtfpl.net/txt/copying')]).
   46:- license(wtfpl).
 defvar(Var:term) is det
Since we are abandoning our high-level discipline, why not start declaring our variables? defvar/1 allows you to declare one empty d-variable (but most of the times it is pointless). Nevertheless, it demonstrates the basic structure of our variables: v(_value) (where v stands for eVil and Variable)
?- defvar X.
X = v(_G666).
   59defvar v(_).
 X:var := Y:var is det
':='/2 will assign the value Y to X. If Y contains instances of X, they will be replaced by its value to avoid cyclic terms Note that X can be a d-variable (empty or not) or a non-instantiated variable.
?- X := 42.
X = v(42).
?- X := 42, print(X), X := 17, print(X).
4217
X = v(17).
?- defvar(X), X := 42.
X = v(42).
?-X:=1+1.
X = v(1+1)
?- X:=1, X:=X+1.
X = v(1+1)
?- X:=1, X := X+1+v(2)+v(3+v(32)).
X = v(1+1+v(2)+v(3+v(32))).
See also
- ':=:'/2
   84X := Y :- (    var(X) -> X = v(Y)
   85          ;              ( replace_x(X,Y,YMX),
   86                           setarg(1,X,YMX) ) ).
 :=:(X:var, Y:term) is det
':=:'/2 behaves similarly to ':='/2 but evaluates the expression Y before assigning it to X.
?- X :=: 1.
X = v(1).
?- X :=: 1+1.
X = v(2).
?- X := 1+1.
X = v(1+1).
?- X:=1, X :=: X+1.
X = v(2).
?- X:=1, X :=: X+1+v(2)+v(3+v(32)).
X = v(39).
See also
- ':='/2
  107X :=: Y :- YY iss Y,
  108           ( X = v(YY) -> true
  109           ;              setarg(1,X,YY) ).
 iss(Y:var, X:term) is det
iss/2 evaluates the expression X and assigns (non-destructively) the value to Y.
?- Y iss 1+v(2)+v(3+v(32)).
Y = 38.
?- v(Y) iss 1+v(2)+v(3+v(32)).
false.
  124Y iss X :- term_to_atom(X,A),
  125           atom_chars(A,C),
  126           phrase(var_term(PC),C),
  127           atom_chars(PA,PC),
  128           atom_to_term(PA,T,[]),
  129           Y is T,!.
 ++(X:var) is semidet
Adds one to the value of a d-variable. If the d-variable is empty, an exception will be thrown.

Usage (covering ++/1, --/1, -:-/1, and +:+/1):

?- X := 1, X++ .
X = v(1+1).
?- X := 1, ++X .
X = v(1+1).
?- X := 1, +:+X.
X = v(2).
?- X := 1, X++, X++ .
X = v(1+1+1).
?- X := 1, X++, X++, +:+X.
X = v(4).
See also
- +:+/1
- --/1
- -:-/1
  153(X ++) :- vcheck(X), X := X + 1.
 +:+(X:var) is semidet
Adds one to the value of a d-variable after evaluating it. If the d-variable is empty, an exception will be thrown.
See also
- --/1
- +:+/1
- -:-/1
  163(X +:+) :- vcheck(X), X :=: X + 1.
 --(X:var) is semidet
Subtracts one from the value of a d-variable. If the d-variable is empty, an exception will be thrown.
See also
- ++/1
- +:+/1
- -:-/1
  173(X --) :- vcheck(X), X := X - 1.
  174%
  175%% -:-(X:var) is semidet.
  176%
  177%  Subtracts one from the value of a d-variable after evaluating it.  If the
  178%  d-variable is empty, an exception will be thrown.
  179%
  180%  @see ++/1
  181%  @see --/1
  182%  @see +:+/1
  183(X -:-) :- vcheck(X), X :=: X - 1.
  184
  185% Auxilliary predicates.  You are not meant to understand these.  They are
  186% evil.  Just trust us on this.
  187
  188vcheck(v(X)):- ( var(X) -> throw('Arguments are not sufficiently instantiated')
  189               ;           true ).
  190
  191var_term([]) -->     [].
  192var_term(PC) -->     [v,'('], { ! },
  193                     var_term(PC1),
  194                     [')'], { ! },
  195                     var_term(PC2),
  196                     { append(PC1, PC2, PC) }.
  197var_term([X|PC]) --> [X],
  198                     var_term(PC).
  199
  200replace_x(X,Y,YMX):- term_chars(Y, YC),
  201                     term_chars(X, XC),
  202                     XC = ['v'| Value],
  203                     phrase(del_x(PC, {XC, Value}), YC),
  204                     term_chars(YMX, PC), !.
  205
  206del_x([], _) --> [].
  207del_x(PC, {XC, Value}) --> XC, { ! },
  208                           del_x(PCT, {XC, Value}),
  209                           { append(Value, PCT, PC) }.
  210del_x([X|PC], XC) -->      [X],
  211                           del_x(PC, XC).
  212
  213term_chars(T, C):- var(C),
  214                   term_to_atom(T, A),
  215                   atom_chars(A, C).
  216term_chars(T, C):- var(T),
  217                   atom_chars(A, C),
  218                   atom_to_term(A, T, [])