History variables

From Rosetta Code
Revision as of 07:19, 24 June 2012 by rosettacode>Gerard Schildberger (→‎{{header|REXX}}: made REXX example compliant. -- ~~~~)
Task
History variables
You are encouraged to solve this task according to the task description, using any language you may know.

Storing the history of objects in a program is a common task. Maintaining the history of an object in a program has traditionally required programmers either to write specific code for handling the historical data, or to use a library which supports history logging.

History variables are variables in a programming language which store not only their current value, but also the values they have contained in the past. Some existing languages do provide support for history variables. However these languages typically have many limits and restrictions on use of history variables.

"History Variables: The Semantics, Formal Correctness, and Implementation of History Variables in an Imperative Programming Language" by Mallon and Takaoka

Concept also discussed on LtU and Patents.com.

Task

Demonstrate History variable support:

  • enable history variable support (if needed)
  • define a history variable
  • assign three values
  • non-destructively display the history
  • recall the three values.

For extra points, if the language of choice does not support history variables, demonstrate how this might be implemented.

Ada

Ada does not natively support history variables -- we have to implement them.

Furthermore, Ada is a strongly typed language -- that means, we would need to write a history variable type for every basic item type. Instead, we write a single generic package "History_Variables" that works for any item type.


Generic Package "History_Variables"

Specification:

<lang Ada>private with Ada.Containers.Indefinite_Vectors; generic

  type Item_Type (<>) is private;

package History_Variables is

  type Variable is tagged limited private;
  -- set and get current value
  procedure Set(V: in out Variable; Item: Item_Type);
  function Get(V: Variable) return Item_Type;
  -- number of items in history (including the current one)
  function Defined(V: Variable) return Natural;
  -- non-destructively search for old values
  function Peek(V: Variable; Generation: Natural := 1) return Item_Type;
  -- V.Peek(0) returns current value; V.Peek(1) the previous value, ect.
  -- when calling V.Peek(i), i must be in 0 .. V.Defined-1, else Constraint_Error is raised
  -- destructively restore previous value
  procedure Undo(V: in out Variable);
  -- old V.Peek(0) is forgotten, old V.Peek(i) is new V.Peek(i-1), ect.
  -- accordingly, V.Defined decrements by 1
  -- special case: if V.Defined=0 then V.Undo does not change V

private

  package Vectors is new Ada.Containers.Indefinite_Vectors
    (Index_Type   => Positive,
     Element_Type => Item_Type);
  type Variable is tagged limited record
     History: Vectors.Vector;
  end record;

end History_Variables;</lang>

The implementation of "History_Variables":

<lang Ada>package body History_Variables is

  -- set and get
  procedure Set(V: in out Variable; Item: Item_Type) is
  begin
     V.History.Prepend(Item);
  end Set;
  function Get(V: Variable) return Item_Type is
  begin
     return V.History.First_Element;
  end Get;
  -- number of items in history (including the current one)
  function Defined(V: Variable) return Natural is
  begin
     return (1 + V.History.Last_Index) - V.History.First_Index;
  end Defined;
  -- non-destructively search
  function Peek(V: Variable; Generation: Natural := 1) return Item_Type is
     Index: Positive  := V.History.First_Index + Generation;
  begin
     if Index > V.History.Last_Index then
        raise Constraint_Error;
     end if;
     return V.History.Element(Index);
  end Peek;
  procedure  Undo(V: in out Variable) is
  begin
     V.History.Delete_First;
  end Undo;

end History_Variables;</lang>


Sample 1: The History of an Integer Variable

<lang Ada>with Ada.Text_IO, History_Variables;

procedure Test_History is

  package Int_With_Hist is new History_Variables(Integer);
  -- define a history variable
  I: Int_With_Hist.Variable;
  Sum: Integer := 0;

begin

  -- assign three values
  I.Set(3);
  I.Set(I.Get + 4);
  I.Set(9);
  -- non-destructively display the history
  for N in reverse 0 .. I.Defined-1 loop
     Ada.Text_IO.Put(Integer'Image(I.Peek(N)));
  end loop;
  Ada.Text_IO.New_Line;
  -- recall the three values
  while I.Defined > 0 loop
     Sum := Sum + I.Get;
     I.Undo;
  end loop;
  Ada.Text_IO.Put_Line(Integer'Image(Sum));

end Test_History;</lang>

The program generates the following output:

 3 7 9
 19


Sample 2: The History of a String

<lang Ada>with Ada.Text_IO, History_Variables;

procedure Test_History is

  package Str_With_Hist is new History_Variables(String);
  -- define a history variable
  S: Str_With_Hist.Variable;
  Sum: Integer := 0;

begin

  -- assign three values
  S.Set("one");
  S.Set(S.Get & S.Get); --"oneone"
  S.Set("three");
  -- non-destructively display the history
  for N in reverse 0 .. S.Defined-1 loop
     Ada.Text_IO.Put(S.Peek(Generation => N) &" ");
  end loop;
  Ada.Text_IO.New_Line;
  -- recall the three values
  while S.Defined > 0 loop
     Sum := Sum + S.Get'Length;
     S.Undo;
  end loop;
  Ada.Text_IO.Put_Line(Integer'Image(Sum));

end Test_History;</lang>

This time, the output is:

one oneone three 
 14

C#

<lang c sharp>using System; using System.Collections; using System.Collections.Generic; using System.Linq;

namespace History {

   class Program
   {
       static void Main(string[] args)
       {
           var h = new HistoryObject();
           h.Value = 5;
           h.Value = "foo";
           h.Value += "bar";
           var history = h.ToArray();
           for (int i = 0; i < history.Length; i++)
           {
               Console.Write("{0}{1}", history[i], ((i >= history.Length - 1) ? "\n" : " <- "));
           }
           h.Undo();
           h.Undo();
           h.Undo();
           Console.WriteLine(h.Value);
       }
       private class HistoryObject : IEnumerable<object>
       {
           public HistoryObject()
           {
               _history = new Stack<object>(); // Initiates the history stack.
           }
           public object Value
           {
               get // Returns the top value from the history if there is one. Otherwise null.
               {
                   if (_history.Count > 0)
                       return _history.Peek();
                   return null;
               }
               set { _history.Push(value); } // Adds the specified value to the history.
           }
           public void Undo()
           {
               if (_history.Count > 0)
                   _history.Pop(); // Removes the current value from the history.
           }
           // History stack that will hold all previous values of the object.
           private readonly Stack<object> _history;
           public IEnumerator<object> GetEnumerator()
           {
               return _history.GetEnumerator();
           }
           IEnumerator IEnumerable.GetEnumerator()
           {
               return GetEnumerator();
           }
       }
   }

}</lang>

Sample Output

foobar <- foo <- 5

Go

We're all in this for the extra points. Mallon and Takota seem happy with sequences, but time and timestamps were mentioned on LtU. Beyond a separate sequence for each history variable, timestamps enable multiple variables to be seen in a common temporal sequence. In Go, with it's attention to concurrency, this might be done with flexibility for proper handling of shared variables, and efficient handling of variables limited to a single thread. <lang go>package main

import (

   "fmt"
   "sort"
   "sync"
   "time"

)

// data type for history variable (its an int) type history struct {

   timestamp tsFunc
   hs        []hset

}

// data type for timestamp generator type tsFunc func() time.Time

// data type for a "set" event type hset struct {

   int           // new value
   t   time.Time // timestamp

}

// newHistory creates a history variable func newHistory(ts tsFunc) history {

   return history{ts, []hsetTemplate:T: ts()}

}

// int returns the current value func (h history) int() int {

   return h.hs[len(h.hs)-1].int

}

// set does what you expect and returns the timestamp recorded for the event func (h *history) set(x int) time.Time {

   t := h.timestamp()
   h.hs = append(h.hs, hset{x, t})
   return t

}

// dump displays a complete history func (h history) dump() {

   for _, hs := range h.hs {
       fmt.Println(hs.t.Format(time.StampNano), hs.int)
   }

}

// recall recalls the value stored in the history variable at time t. // if the variable had not been created yet, ok is false. func (h history) recall(t time.Time) (int, /*ok*/ bool) {

   i := sort.Search(len(h.hs), func(i int) bool {
       return h.hs[i].t.After(t)
   })
   if i > 0 {
       return h.hs[i-1].int, true
   }
   return 0, false

}

// newTimestamper returns a function that generates unique timestamps. // Use a single timestamper for multiple history variables to preserve // an unambiguous sequence of assignments across the multiple history // variables within a single goroutine. func newTimestamper() tsFunc {

   var last time.Time
   return func() time.Time {
       if t := time.Now(); t.After(last) {
           last = t
       } else {
           last.Add(1)
       }
       return last
   }

}

// newProtectedTimestamper generates unique timestamps for concurrent // goroutines. func newProtectedTimestamper() tsFunc {

   var last time.Time
   var m sync.Mutex
   return func() (t time.Time) {
       t = time.Now()
       m.Lock() // m protects last
       if t.After(last) {
           last = t
       } else {
           last.Add(1)
           t = last
       }
       m.Unlock()
       return
   }

}

func main() {

   // enable history variable support appropriate for single goroutine.
   ts := newTimestamper()
   // define a history variable
   h := newHistory(ts)
   // assign three values.  (timestamps kept for future reference.)
   ref := []time.Time{h.set(3), h.set(1), h.set(4)}
   // non-destructively display history
   fmt.Println("History of variable h:")
   h.dump() 
   // recall the three values.  (this is non-destructive as well, but
   // different than the dump in that values are recalled by time.)
   fmt.Println("Recalling values:")
   for _, t := range ref {
       rv, _ := h.recall(t)
       fmt.Println(rv)
   }

}</lang> Output:

History of variable h:
Dec  3 18:51:17.292260000 0
Dec  3 18:51:17.292262000 3
Dec  3 18:51:17.292264000 1
Dec  3 18:51:17.292270000 4
Recalling values:
3
1
4

Haskell

There are no native Haskell history variables, but they are simple to implement.

<lang haskell>import Data.IORef

newtype HVar a = HVar (IORef [a])

newHVar :: a -> IO (HVar a) newHVar value = fmap HVar (newIORef [value])

readHVar :: HVar a -> IO a readHVar (HVar ref) = fmap head (readIORef ref)

writeHVar :: a -> HVar a -> IO () writeHVar value (HVar ref) = modifyIORef ref (value:)

undoHVar :: HVar a -> IO () undoHVar (HVar ref) = do

   (_ : history) <- readIORef ref
   writeIORef ref history

getHistory :: HVar a -> IO [a] getHistory (HVar ref) = readIORef ref

-- Testing main :: IO () main = do

   var <- newHVar 0
   writeHVar 1 var
   writeHVar 2 var
   writeHVar 3 var
   getHistory var >>= print
   undoHVar var
   undoHVar var
   undoHVar var</lang>

J

J does not natively support "history variables", but the functionality is easy to add:

<lang j>varref_hist_=:'VAR','_hist_',~] set_hist_=:4 :0

 V=.varref x
 if.0>nc<V do.(<V)=:end.
 (<V)=.V~,<y
 y

) getall_hist_=:3 :0

 (varref y)~

) length_hist_=: #@getall get_hist_=: _1 {:: getall</lang>

Example use:

<lang j> 'x' set_hist_ 9 9

  'x' set_hist_ 10

10

  'x' set_hist_ 11

11

  get_hist_ 'x'

11

  length_hist_ 'x'

3

  getall_hist_ 'x'

┌─┬──┬──┐ │9│10│11│ └─┴──┴──┘</lang>

Note that each value is contained in a box, so different values do not need to be type compatible with each other. If this is considered a defect then assertions could be added to enforce type compatibility across assignments.

Note that only nouns are supported here: If you want to store verbs using this mechanism you will need to use their gerunds.

OxygenBasic

Simple history class for fixed length types that do not contain volatile pointer members. <lang oxygenbasic> '============ class History '============

indexbase 0

string buf sys ii,ld,pb

method constructor(sys n=1000, l=sizeof sys) {buf=nuls n*l : pb=strptr buf : ld=l : ii=0} method destructor () {clear} ' method setup(sys n=1000, l=sizeof sys) {buf=nuls n*l : pb=strptr buf : ld=l : ii=0} method clear() {buf="" : pb=0 : ld=0 : ii=0} method max (sys i) {if i>ii{ii=i}} method count() as sys {return ii} method size () as sys {return ld} ' method get (any*p,i) {copy @p, pb+i*ld,ld } 'out method add (any*p) {copy pb+ii*ld,@p,ld : ii++} 'in method put (any*p,sys i) {copy pb+i*ld,@p,ld : max i} 'in ' end class

'==== 'TEST '====

'this works for fixed length types

'it will not work for types containing 'volatile pointers. eg: string members

type vector double x,y,z

vector v

new History hv(1000,sizeof v) 'give number of records and variable size

sys i for i=0 to 9

 v<=i,i*10,i*100 'assign new values to vector
 hv.add v      'add to history

next

string tab=chr(9) : cr=chr(13)+chr(10) string pr="Data History of v" cr cr pr+="n" tab "x" tab "y" tab "z" cr vector sv ' for i=hv.count()-1 to 0 step -1

 hv.get sv,i
 pr+=i tab sv.x tab sv.y tab sv.z cr

next

print pr 'result '9,90,900 : 8,80,800 ...

del hv </lang>

PARI/GP

<lang parigp>default(histsize, 1000) \\ or some other positive number to suit 1+7 sin(Pi) 2^100 \a1 \\ display history item #1, etc. % \\ alternate syntax %1 \\ alternate syntax \a2 \a3 [%1, %2, %3] \\ or any other command using these values</lang>

Perl

Implemented via tie (and what's the usefulness of this?) <lang Perl>package History;

sub TIESCALAR { my $cls = shift; my $cur_val = shift; return bless []; }

sub FETCH { return shift->[-1] }

sub STORE { my ($var, $val) = @_; push @$var, $val; return $val; }

sub get(\$) { @{tied ${+shift}} } sub on(\$) { tie ${+shift}, __PACKAGE__ } sub off(\$) { untie ${+shift} } sub undo(\$) { pop @{tied ${+shift}} }

package main;

my $x = 0; History::on($x);

for ("a" .. "d") { $x = $_ }

print "History: @{[History::get($x)]}\n";

for (1 .. 3) { print "undo $_, "; History::undo($x); print "current value: $x\n"; }

History::off($x); print "\$x is: $x\n";</lang>Output<lang>History: a b c d undo 1, current value: c undo 2, current value: b undo 3, current value: a $x is: a</lang>

Python

<lang Python>import sys

HIST = {}

def trace(frame, event, arg):

   for name,val in frame.f_locals.items():
       if name not in HIST:
           HIST[name] = []
       else:
           if HIST[name][-1] is val:
               continue
       HIST[name].append(val)
   return trace

def undo(name):

   HIST[name].pop(-1)
   return HIST[name][-1]

def main():

   a = 10
   a = 20
   for i in range(5):
       c = i
   print "c:", c, "-> undo x3 ->",
   c = undo('c')
   c = undo('c')
   c = undo('c')
   print c
   print 'HIST:', HIST

sys.settrace(trace) main()</lang>Output<lang>c: 4 -> undo x3 -> 1 HIST: {'a': [10, 20], 'i': [0, 1, 2, 3, 4], 'c': [0, 1], 'name': ['c']}</lang>

PicoLisp

<lang PicoLisp>(de setH ("Var" Val)

  (when (val "Var")
     (with "Var"
        (=: history (cons @ (: history))) ) )
  (set "Var" Val) )

(de restoreH ("Var")

  (set "Var" (pop (prop "Var" 'history))) )</lang>

Test:

: (setH 'A "Hello world")
-> "Hello world"

: (setH 'A '(a b c d))
-> (a b c d)

: (setH 'A 123)
-> 123

: A
-> 123

: (get 'A 'history)
-> ((a b c d) "Hello world")

: (restoreH 'A)
-> (a b c d)

: (restoreH 'A)
-> "Hello world"

: A
-> "Hello world"

: (restoreH 'A)
-> NIL

PL/I

<lang PL/I> declare t float controlled;

do i = 1 to 5; /* a loop to read in and save five values. */ allocate t; get (t); end;

do while (allocation(t) > 0); /* a loop to retrieve the values. */ put (t); free t; end; </lang>

Protium

<lang protium>Turn history on <@ DEFHST>__on</@> Notify Protium we are interested in the variable mv <@ DEFHST>mv</@> Assign a value: <@ LETVARLIT>mv|first value</@><@ SAYVAR>mv</@> Reassign the value: <@ LETVARLIT>mv|second value</@><@ SAYVAR>mv</@> Reassign the value: <@ LETVARLIT>mv|third value</@><@ SAYVAR>mv</@> Dump history <@ SAYDMPHSTVAR>mv</@> Current value: <@ SAYVAR>mv</@> Undo once: <@ ACTUNDVAR>mv</@><@ SAYVAR>mv</@> Undo twice: <@ ACTUNDVAR>mv</@><@ SAYVAR>mv</@> Turn history off <@ DEFHST>__off</@></lang>

Same code, Simplified Chinese dialect <lang protium>Turn history on <# 定义变量史>__on</#> Notify Protium we are interested in the variable mv <# 定义变量史>mv</#> Assign a value: <# 指定变量字串>mv|first value</#><# 显示变量>mv</#> Reassign the value: <# 指定变量字串>mv|second value</#><# 显示变量>mv</#> Reassign the value: <# 指定变量字串>mv|third value</#><# 显示变量>mv</#> Dump history <# 显示全内容变量史变量>mv</#> Current value: <# 显示变量>mv</#> Undo once: <# 运行撤消变量>mv</#><# 显示变量>mv</#> Undo twice: <# 运行撤消变量>mv</#><# 显示变量>mv</#> Turn history off <# 定义变量史>__off</#> </lang>

Sample output

Turn history on  
Notify Protium we are interested in the variable mv 
 
Assign a value: first value 
Reassign the value: second value 
Reassign the value: third value 
Dump history third value^second value^first value^ 
Current value: third value
Undo once: second value 
Undo twice: first value 
Turn history off  

REXX

The REXX language doesn't support histories, but can be coded with little trouble.

The history list part of the VARSET subroutine could be seperated into its
own if you wanted to keep the subroutine's function pure. <lang rexx> /*REXX pgm shows a method to track history of assignments to a REXX var.*/ varset!.=0 /*initialize the whole shebang. */

call varset 'fluid',min(0,-5/2,-1)  ; say 'fluid=' fluid call varset 'fluid',3.14159  ; say 'fluid=' fluid call varset 'fluid',' Santa Claus'  ; say 'fluid=' fluid

call varset 'fluid',,999 say 'There were' result "assignments (sets) for the FLUID variable." exit /*─────────────────────────────────────VARSET subroutine────────────────*/ varset: arg ?x; parse arg ?z,?v,?L /*varName, value, optional-List. */

if ?L== then do /*not list, so set the X variable*/

              ?_=varset!.0.?x+1       /*bump the history count (SETs). */
              varset!.0.?x=?_         /* ... and store it in "database"*/
              varset!.?_.?x=?v        /* ... and store the  SET  value.*/
              call value(?x),?v       /*now, set the real  X  variable.*/
              return ?v               /*also, return the value for FUNC*/
              end

say /*show blank line for readability*/

 do ?j=1 to ?L while ?j<=varset!.0.?x      /*list history of the sets. */
 say 'history entry' ?j "for var" ?z":" varset!.?J.?x
 end

return ?j-1 /*return the num of assignments. */</lang> output

fluid= -2.5
fluid= 3.14159
fluid=  Santa  Claus

history entry 1 for var fluid: -2.5
history entry 2 for var fluid: 3.14159
history entry 3 for var fluid:  Santa  Claus
There were 3 assignments (sets) for the FLUID variable.

Scala

Scala doesn't have a native support for history variables, but it's quite easy to implement them. The following class uses same conventions as ML's mutable reference cells. (i.e. ! as accessor, and := as mutator.) <lang scala>class HVar[A](initialValue: A) extends Proxy {

 override def self = !this
 override def toString = "HVar(" + !this + ")"
 
 def history = _history
 private var _history = List(initialValue)
 def unary_! = _history.head
 def :=(newValue: A): Unit = {
   _history = newValue :: _history
 }
 def modify(f: A => A): Unit = {
   _history = f(!this) :: _history
 }
 def undo: A = {
   val v = !this
   _history = _history.tail
   v
 }

}</lang> Usage: <lang scala>scala> val h = new HVar(3) h: HVar[Int] = HVar(3)

scala> h := 11

scala> h := 90

scala> !h res32: Int = 90

scala> h.history res33: List[Int] = List(90, 11, 3)

scala> h.undo res34: Int = 90

scala> h.undo res35: Int = 11

scala> h.undo res36: Int = 3</lang>

Tcl

Though Tcl's variables don't have history by default, it can be added easily through the use of traces: <lang tcl># Define the history machinery proc histvar {varName operation} {

   upvar 1 $varName v ___history($varName) history
   switch -- $operation {

start { set history {} if {[info exist v]} { lappend history $v } trace add variable v write [list histvar.write $varName] trace add variable v read [list histvar.read $varName] } list { return $history } undo { set history [lrange $history 0 end-1] } stop { unset history trace remove variable v write [list histvar.write $varName] trace remove variable v read [list histvar.read $varName] }

   }

} proc histvar.write {key varName args} {

   upvar 1 $varName v ___history($key) history
   lappend history $v

} proc histvar.read {key varName args} {

   upvar 1 $varName v ___history($key) history
   set v [lindex $history end]

}</lang> Demonstrating how to use it: <lang tcl># Enable history for foo histvar foo start set foo {a b c d} set foo 123 set foo "quick brown fox" puts $foo puts foo-history=[join [histvar foo list] ", "] puts $foo histvar foo undo puts $foo histvar foo undo puts $foo histvar foo stop</lang> Output:

quick brown fox
foo-history=a b c d, 123, quick brown fox
quick brown fox
123
a b c d