!MINIMO: multiple output logic function minimiser
!
!        Hamish Dewar 1981
!
include "inc:util.imp"
begin
constinteger outstream=1
! Codes for logical operators
constinteger not=-1, or=-2, and=-3;   !(OR-1=AND)
! Flag-bit
constinteger sign=16_80000000, forced=16_40000000

! Control parameters
owninteger min=4096
owninteger inc=4096
owninteger echo=0;              !copy input to output stream
owninteger squash=0;            !compress output tables
owninteger nin=0;               !negate input variables
owninteger nout=0;              !negate output variables
owninteger check=0;             !check completeness
owninteger mon=0;               !monitoring selector (bits)
owninteger single=0;            !apply single (rather than multiple) method
owninteger tabin=0;             !tabular input

owninteger instream=3

integer negin,ignorin,negout,ignorout
integer count,aim;              !current,target score
integer minsep;                 !minimum free space in array W
integer sym
integer start

constinteger storebound=2000
integer dclim,esslim,sp1,sp,np,np1;       !index vars to array W
integer needsp
recordformat cell(integer t,f,outs,flags)
record(cell) array w(1:storebound);       !stack -> <- nest

constinteger namebound=256
integer inmax,outmin,namemax;             !index vars to NAME,EXP
string(7)array name(1:namebound)
integerarray exp(1:namebound)

constinteger defbound=8192
integer dp
integerarray def(1:defbound)

integerfn bits(integer v)
integer k
k = 0
k = 1 and v = v<<1>>1 if v < 0
while v # 0 cycle
  k = k+1
  v = v&(v-1)
repeat
result = k
end

routine out(integer v)
  out(v//10) and v = v-v//10*10 if v >= 10
  printsymbol(v+'0')
end

routine croak(string(32) s)
  select output(0)
  newline
  printstring("*".s."  Abandoned")
  if sym # nl start
    printstring(" at: ")
    cycle
      readsymbol(sym)
      printsymbol(sym)
    repeat until sym = nl
  finish
  stop
end

routine print time
integer t
  t = cputime
  print((t-start)/1000,5,3)
  start = t
end

routine push(record(cell) v)
! Store V on (descending) nest
  np = np-1;  w(np) = v
  return if np-sp >= minsep
  minsep = np-sp
  return if minsep > 2
  croak("No space.")
end

routine stack(record(cell) v)
! Store V on (ascending) stack
  w(sp) = v;  sp = sp+1
  return if np-sp > minsep
  minsep = np-sp
  return if minsep > 2
  croak("No space.")
end

! R e a d   a n d   c h e c k   d a t a
!
routine readin
integer bit,pos,pos1,found,first,dp1,outmax
integer pend
string(7) curname

routine put(integer v)
  croak(" Definitions too long") if dp > defbound
  def(dp) = v;  dp = dp+1
end

routine read sym
  on event 9 start
    sym = '*'
    instream = instream-1
    return if instream = 0
    if instream < 0 start
      sym = nl
      croak("Premature end of input.")
    finish
    select input(instream)
  finish
  sym = pend;  pend = 0
  return if sym # 0
  cycle
    readsymbol(sym)
    printsymbol(sym) if echo # 0
    return unless sym = '{'
    cycle
      read symbol(sym)
      print symbol(sym) if echo # 0
    repeat until sym = '}'
  repeat
end

routine read name
!Read name (possibly null) to CURNAME leaving terminator in SYM
integer k,l
  read sym until sym > ' '
  l = 0
  k = sym;  k = k-'a'+'A' if k >= 'a'
  if 'A' <= k <= 'Z' start
    cycle
      if l < 6 start
        l = l+1;  charno(curname,l) = k
      finish
      read sym
      k = sym;  k = k-'a'+'A' if k >= 'a'
      exit unless '0' <= k <= '9' c
            or (charno(curname,l) >= 'A' and 'A' <= k <= 'Z')
    repeat
    if sym = '?' start
      l = l+1;  charno(curname,l) = sym
      read sym
    finish
  finish
  length(curname) = l
  if sym=' ' start
    read sym until sym#' '
    if 'A'<=sym&95<='Z' start
      pend = sym; sym = ' '
    finish
  finish
end

routine init(integername v)
! Read asignment for mode variable V (default 1)
  found = 1
  v = 1
  read(v) and out(v) if sym = '='
end

routine lookup
  pos = namemax+1
  pos = pos-1 until pos = 0  or name(pos) = curname
end

routine queryname
  newline if echo # 0
  printstring(curname." not known")
  newline
end

routine addname
  namemax = namemax+1
  name(namemax) = curname
end

routine newname
  croak("Duplicate: ".curname.". ") if pos # 0
  addname
end

routine read exp
! Read logic expression: store as Polish
!   operands represented as name index values (> 0)
!   operators < 0
!  eg A&B ! ¬A&¬B  ==>  1 2 AND NOT 1 NOT NOT 2 NOT AND OR 0
!                       A B  &   ¬  A  ¬   ¬  B  ¬   &   !
!  note duplication of NOT before and after

routine read term
  read name
  if curname # "" start
    pend = sym if sym >= 'A' or sym = '('
    lookup
    queryname and pos = 1 if pos = 0
    put(pos)
  finish else if sym = '¬' start
    put(not);                           !fore ..
    read term
    put(not);                           ! .. as well as aft
  finish else start
    croak("Faulty format. ") if sym # '('
    read exp
    croak("Missing ')'. ") if sym # ')'
    read sym
  finish
end

routine read exp1
  read term
  while sym = '&' or sym = '.' or sym >= 'A' or sym = '(' cycle
    read term
    put(and)
  repeat
end

  read exp1
  while sym = '!' or sym = '+' cycle
    read exp1
    put(or)
  repeat
end;  !READ EXP

  namemax = 0;  dp = 1
  pend = 0
! MODE settings (if any)
  cycle
    read name
    stop if sym = '*'
    exit unless curname = "MODE"
    printstring("MODE ") and printsymbol(pend) if echo=0
    echo = echo-2
    cycle
      read name
      found = 0
      init(nin) if curname = "NIN"
      init(nout) if curname = "NOUT"
      init(min) if curname = "MIN"
      init(inc) if curname = "INC"
      init(echo) if curname = "ECHO"
      init(squash) if curname = "SQUASH"
      init(check) if curname = "CHECK"
      init(mon) if curname = "MON"
      init(single) if curname = "SINGLE"
      init(tabin) if curname = "TABIN"
      init(tabin) and tabin = 1-tabin if curname="EQUIN"
      printsymbol('?') if found = 0
    repeat until sym # ','
    if echo<0 start
      echo = echo+2
      newline if echo=0
    finish
  repeat
! INput list
  croak("Keyword ".curname."? ") if curname # "IN"
  pend = sym if pend=0
  bit = 1;  negin = 0;  ignorin = 0
  cycle
    croak("Too many inputs.") if bit = 0
    read sym until sym>' ' and sym#','
    if sym = '-' start
      ignorin = ignorin+bit
      curname = "-"
      read sym
    finish else start
      if sym = '¬' then negin = negin+bit c
      else pend = sym
      read name
      lookup
    finish
    newname
    exp(namemax) = bit
    bit = bit<<1
  repeat until sym # ','
  inmax = namemax
  negin = ¬negin if nin # 0
! logic equations
if tabin = 0 start
  cycle
    read name
    exit if sym # '='
    lookup
    pos = 0 if pos <= inmax
    newname
    exp(namemax) = dp;                  !start of Polish representation
    namemax = namemax-1;                !hide LH name to exclude self-ref
    read exp
    namemax = namemax+1;                !restore LH name
    put(0);                             !terminator
    croak("Faulty format. ") if sym # nl
  repeat
finish else start;                      !tabular input
  pos1 = namebound+1;  outmax = 0
  cycle
    read sym until sym > ' '
    pend=sym and exit if sym&95 = 'O'
    pos1 = pos1-1
    croak("Too many table entries") if pos1 = namemax
    exp(pos1) = 0
    first = 1
    for pos = 1,1,inmax cycle
      if ignorin>>(pos-1)&1 = 0 c
      and (sym = '0' or sym = '1') start
        if sym = '1' then put(pos) c
        else put(not) and put(pos) and put(not)
        put(and) if first = 0
        first = 0
      finish
      read sym until sym # ' '
    repeat
    put(0)
    bit = 1;  namemax = inmax
    while sym # nl cycle
      croak("Faulty entry. ") if (sym # '0' and sym # '1') c
           or namemax = outmax
      exp(pos1) = exp(pos1)!bit if sym = '1'
      bit = bit<<1;  namemax = namemax+1
      read sym until sym # ' '
    repeat
    outmax = namemax if outmax = 0
    croak("Faulty entry. ") if outmax # namemax
  repeat
  bit = 1
  bit = ¬0 and namemax = inmax+1 if check # 0
  for pos = inmax+1,1,namemax cycle
    exp(pos) = dp
    first = 1
    for pos1 = namebound,-1,pos1 cycle
      if exp(pos1)&bit # 0 start
        put(pos1)
        put(or) if first = 0
        first = 0
      finish
    repeat
    put(0)
    bit = bit<<1
  repeat
  dp1 = 1
  for pos1 = namebound,-1,pos1 cycle
    exp(pos1) = dp1
    dp1 = dp1+1 until def(dp1-1) = 0
  repeat
  read name
finish
! OUTput list
!  note that OUTput names are added again 
!      to simplify treatment of "Don't cares"
  croak("Keyword ".curname."? ") if curname # "OUT"
  pend = sym if pend=0
  outmin = namemax+1;  pos = inmax
  negout = 0;  ignorout = 0;  bit = 1
  cycle
    croak("Too many outputs. ") if namemax-outmin+2 > 32
    read sym until sym>' ' and sym#','
    if sym = '-' start
      ignorout = ignorout+bit
      curname = "-"
      read sym
    finish else start
      if sym = '¬' then negout = negout+bit c
      else pend = sym
      read name
    finish
    if tabin = 0 then lookup else pos = pos+1
    if pos # 0 start;                   !should be there
      addname
      exp(namemax) = dp
      put(pos)
      if tabin = 0 start
        curname = curname."?";          !any "Don't cares" for this one?
        lookup
        if pos # 0 start;               !if so
          put(pos)
          put(or)
        finish
      finish
      put(0)
    finish else start
      queryname
    finish
    bit = bit<<1
  repeat until sym # ','
  stop if outmin > namemax;             !no (surviving) outputs
  croak("Faulty format. ") if sym # nl
  negout = ¬negout if nout # 0
end;  !READIN

routine print term(record(cell) v, integer x)
integer i,l
  for i = 1,1,inmax cycle
    space if squash = 0
    if (v_t!v_f)&1 # 0 start
      l = ' '
      l = '¬' if v_f&1 # 0
      printsymbol(l)
      print string(name(i))
    finish else start
      l = length(name(i))
      spaces((l+1)//2)
      printsymbol('.')
      spaces(l//2)
    finish
    v_t = v_t>>1;  v_f = v_f>>1
  repeat
  space if squash = 0
  printsymbol(':')
  for i = outmin,1,namemax cycle
    space
    if v_outs&1 # 0 start
      printstring(name(i))
    finish else start
      l = length(name(i))
      spaces((l-1)//2)
      if x&1 = 0 then printsymbol('.') c
      else printsymbol('?')
      spaces(l//2)
    finish
    v_outs = v_outs>>1;  x = x>>1
  repeat
  newline
end

routine monitor(integer lim)
integer q
  newline
  q = 1
  while q # lim cycle
    write(q,2) if mon&4 # 0
    print term(w(q),0)
    q = q+1
  repeat
  newline
end

routine copydown
  np1 = np
  while sp # sp1 cycle
    sp = sp-1;  np = np-1
    w(np) = w(sp)
  repeat
end

routine erase(integer p)
  sp = sp-1
  while p # sp cycle
    w(p) = w(p+1)
    p = p+1
  repeat
end

routine merge
integer p,k,same
ownrecord(cell) v,n=0
  while np # np1 cycle
    v = w(np);  np = np+1
    p = sp1;  same = 0
    while p # sp cycle
      if w(p)_t!v_t = v_t and w(p)_f!v_f = v_f start;    !V -> @P
        v_outs = v_outs&(¬w(p)_outs)
        exit if v_outs = 0
        same = p if w(p)_t = v_t and w(p)_f = v_f
      finish
      p = p+1
    repeat
    if v_outs # 0 start
      while p # sp1 cycle
        p = p-1
        n_outs = w(p)_outs&v_outs
        if n_outs # 0 start
          n_t = w(p)_t!v_t;  n_f = w(p)_f!v_f
          k = (n_t)&n_f
          if k # 0 and (k-1)&k = 0 start;    !singleton
            n_t = n_t!!k;  n_f = n_f!!k
            push(n)
            v_outs = v_outs!!n_outs if n_t!v_t = v_t and n_f!v_f = v_f;   !V -> N
            n_t = n_t!w(p)_t;  n_f = n_f!w(p)_f
          finish
          if n_t = w(p)_t and n_f = w(p)_f start;     !@P -> N
            w(p)_outs = w(p)_outs!!n_outs
            if w(p)_outs = 0 start
              erase(p)
              same = same-1 if same > p
            finish
          finish
          exit if v_outs = 0
        finish
      repeat
      if v_outs # 0 start
        if same = 0 start
          w(sp) = v;  sp = sp+1
        finish else start
          w(same)_outs = w(same)_outs+v_outs
        finish
      finish
    finish
  repeat
end

! C o n v e r t   f r o m   P o l i s h   t o   i n t e r n a l 
!
routine convert
integer outbit,oldsp,i,j,k,p,q,hp,inv
ownrecord(cell) v=0
integerarray hold(1:20)

routine convert(integer j)
integer defp
  defp = exp(j)
  cycle
    j = def(defp);  defp = defp+1;      !get next item
    return if j = 0;                    !terminator
    if j > 0 start;                     !operand
      if j > inmax start;               !start of sub-def
        convert(j)
      finish else start
        hp = hp+1;  hold(hp) = sp1
        sp1 = sp
        v_t = exp(j);  v_f = 0
        v_f = v_t and v_t = 0 if inv!!(negin>>(j-1)&1) # 0
        stack(v)
      finish
    finish else if j = not start
      inv = inv!!1
    finish else if j-inv = and start;      !'AND' or inverted 'OR'
      np1 = np;                         !Form pairwise intersection on nest
      while sp # sp1 cycle
        sp = sp-1
        p = sp1
        while p # hold(hp) cycle
          p = p-1
          v_t = w(sp)_t!w(p)_t;  v_f = w(sp)_f!w(p)_f
          push(v) if v_t&v_f = 0;  !intersection ok
        repeat
      repeat
      sp1 = hold(hp);  hp = hp-1
      sp = sp1;                         !start with stack empty
      merge
    finish else start;                  !'OR' or inverted 'AND'
      copydown;                         !one operand to nest
      sp1 = hold(hp);  hp = hp-1
      merge
    finish
  repeat
end

sp = 1;  np = storebound;  minsep = np-sp
v_flags = 0
outbit = 1
for i = outmin,1,namemax cycle
if ignorout&outbit = 0 start
  k = def(exp(i)+1);                    !2nd element of def
  if k # 0 start;                       !"Don't cares" present
    sp1 = 1;  hp = 0;  inv = 0
    v_outs = outbit
    convert(k)
    copydown
    sp1 = 1
    merge
  finish
finish
outbit = outbit<<1
repeat
dclim = sp
outbit = 1
for i = outmin,1,namemax cycle
if ignorout&outbit = 0 start
  sp1 = 1;  hp = 0;  inv = negout>>(i-outmin)&1
  v_outs = outbit
  convert(i)
  copydown
  sp1 = dclim
  if single # 0 then merge else start
    oldsp = sp
    while np # np1 cycle;               !each element against rest
      q = sp1-1;                        ! and null (ie straight)
      v = 0
      cycle
        v_t = v_t!w(np)_t;  v_f = v_f!w(np)_f
        if v_t&v_f = 0 start
          v_outs = v_outs!outbit
          p = sp
          while p # sp1 cycle
            p = p-1
            v_outs = v_outs!w(p)_outs if w(p)_t = v_t and w(p)_f = v_f
            j = w(p)_t!v_t;  k = w(p)_f!v_f
           exit if j = v_t and k = v_f and w(p)_outs&v_outs = v_outs;     !V -> @P
 if j = w(p)_t and k = w(p)_f and w(p)_outs&v_outs = w(p)_outs start
              oldsp = oldsp-1 if p < oldsp
              q = q-1 if p <= q
              erase(p)
            finish
          repeat
          stack(v) if p = sp1
        finish
        q = q+1
        exit if q = oldsp
        v = w(q)
      repeat
      np = np+1
    repeat
  finish
finish
outbit = outbit<<1
repeat
end;  !convert

integerfn needed(integer q,testlim)
integer p
ownrecord(cell) v,n=0
  sp1 = sp;  np1 = np
  v = w(q)
  w(sp1)_t = v_t;  w(sp1)_f = v_f
  w(sp1)_outs = 0
  sp = sp+1
  p = 1
  while p # testlim cycle
    if w(p)_flags >= 0 start
      n_outs = w(p)_outs&v_outs
      if n_outs # 0 and p # q start
        n_t = w(p)_t!v_t;  n_f = w(p)_f!v_f
        if n_t&n_f = 0 start
          np = np-1;  w(np) = n
          merge
          exit if w(sp1)_outs = v_outs
        finish
      finish
    finish
    p = p+1
  repeat
  needsp = sp
  sp = sp1
  result = p
end

routine print all
integer p,q
  newlines(2)
  q = dclim;  q = esslim if mon&2 # 0
  while q # sp cycle
    if w(q)_flags >= 0 start
      p = needed(q,sp)
      write(q,2) if mon&4 # 0
      w(sp1)_outs = w(q)_outs-w(sp1)_outs
      print term(w(sp1),w(q)_outs)
    finish
    q = q+1
  repeat
  newline
end

routine pcount
  write(count>>12,1)
  printsymbol('/')
  out(count&4095)
end

routine promote(integer q,past)
record(cell) v
  v = w(q)
  if past = 0 start
    count = count+bits(v_t!v_f)+4096
    past = esslim
    esslim = esslim+1
  finish
  while past # esslim and past # dclim cycle
    exit if w(past-1)_flags <= v_flags
    past = past-1
  repeat
  while q # past cycle
    q = q-1
    w(q+1) = w(q)
  repeat
  w(q) = v
end

! R e d u c e   n u m b e r   o f   i m p l i c a n t s
!
routine reduce1
! Find first essentials and redundants
!   order by weight
integer p,q
  q = dclim;  esslim = q
  while q # sp cycle
    w(q)_flags = bits(w(q)_t!w(q)_f)<<5+31-bits(w(q)_outs)
    p = needed(q,sp)
    if p = sp start;                    !essential
      promote(q,0)
    finish else if p >= esslim start;     !optional
      promote(q,q)
    finish else start;     !redundant
      erase(q)
      q = q-1
    finish
    q = q+1
  repeat
end;  !reduce1

routine reduce2
! Find secondary essentials & redundants
integer p,q,bq,sphold,done
record(cell) v
cycle
  done = 1
  q = sp
  while q # esslim cycle
    q = q-1
    p = needed(q,esslim)
    if p = esslim start;                !not (simply) redundant
      w(q)_outs = w(q)_outs-w(sp1)_outs
      w(sp1)_outs = 0
      bq = w(q)_flags>>5
      sphold = sp
      while p # sp cycle
        if w(p)_flags>>5-min < bq and p # q start
          v_outs = w(p)_outs&w(q)_outs
          if v_outs # 0 start
            v_t = w(p)_t!w(q)_t;  v_f = w(p)_f!w(q)_f
            if v_t&v_f = 0 start
              sp1 = sp;  sp = needsp
              while sp1 # needsp cycle
                w(sp) = w(sp1)
                sp = sp+1;  sp1 = sp1+1
              repeat
              push(v)
              merge
              sp = sphold
              exit if w(sp1)_outs = w(q)_outs
            finish
          finish
        finish
        p = p+1
      repeat
    finish
    if p # sp start;                    !redundant
      erase(q)
      p = p-1 if p > q
      if p >= esslim start;             !P may now be essential
        if needed(p,sp) = sp start
          q = q+1 if p >= q
          promote(p,0)
          done = 0
        finish
      finish
    finish
  repeat
repeat until done # 0
end;  !reduce2

routine order
integer j,k,p,q,r,poss,last
integerarray link(1:sp)
record(cell) v
  q = sp;  poss = 0;  last = sp
  while q # esslim cycle
    q = q-1
    p = needed(q,sp)
    link(q) = p
    if p > q and link(p) > p start
      poss = poss+1
      poss = poss+99 if q # last
      v = w(p);  !promote P before Q
      r = sp
      cycle
        r = r-1
        j = link(r)
        if j = p then j = q else if q <= j < p then j = j+1
        if r >= p then start
          link(r) = j
        finish else start
          link(r+1) = j
          w(r+1) = w(r)
        finish
      repeat until r = q
      w(r) = v
      q = q+2;  last = q-1;  !try Q again
    finish
  repeat
  write(poss,1)
!First pass
  cycle
    v = w(q)
    v_flags = v_flags>>5
    p = needed(q,sp)
    if p > q start
      count = count+v_flags+4096
      w(q)_flags = v_flags+count<<5
    finish else start
      cycle
        p = p+1
      repeat until w(p)_flags >= 0
      r = q
      while r # p cycle
        r = r-1
        w(r+1) = w(r)
      repeat
      v_flags = w(r-1)_flags&16_0FFFFFE0+v_flags+sign
      w(r) = v
    finish
    q = q+1
  repeat until q = sp
end;  !order

! F i n d   m i n i m a l   s e l e c t i o n
!
routine minimise
! Find minimal selection
integer k,p,q,m
  q = sp
  cycle
    while q # sp cycle
      m = w(q)_flags
      p = needed(q,sp)
      if p = sp start;                  !mandatory
        m = m+forced
      finish else start;                !optional or redundant
        m = m+(sign+forced) if p < q;   !redundant
      finish
      if m >= 0 start;              !selected
        k = m&31+count+4096
        exit if k+inc > aim
        exit if k+inc > m>>5&16_7FFFFF
        count = k
      finish
      w(q)_flags = m
      q = q+1
    repeat
    if q = sp start;                    !scan completed successfully
      pcount
      printall if inc = 0 or mon&1 # 0
      aim = count
      q = esslim
      while q # sp cycle;               !save marker bits
        k = w(q)_flags&16_cfffffff
        w(q)_flags = (k&16_c0000000)>>2+k
        q = q+1
      repeat
    finish
    cycle;                              !scan backward to de-select
      if q = esslim start;              !scan completed
        while q # sp cycle;             !restore marker bits
          k = w(q)_flags&16_3fffffff
          w(q)_flags = (k&16_30000000)<<2+k
          q = q+1
        repeat
        return if inc <= min;           !all done
        count = aim;                    !restore count
        inc = inc>>1
        print all if inc = 0
      finish
      q = q-1
      m = w(q)_flags
      w(q)_flags = m&16_3fffffff
      if m >= 0 start
        k = m&31+4096
        count = count-k
        exit if m&forced = 0
      finish
    repeat
    w(q)_flags = w(q)_flags+sign
    q = q+1
  repeat
end;  !minimise

begin {initialise}
string(255)in1=":N",in2=":N",in3,out=":T"
integer bools=16_05000000{single,equin}

  routine init(integername n)
    n = 1 if bools<0; bools = bools<<1
  end

  defineparam("Input file",in3,pamnodefault)
  defineparam("Input 2",in2,0)
  defineparam("Input 3",in1,0)
  defineparam("Output file",out,pamnewgroup)
  defineintparam("MIN",min,0)
  defineintparam("INC",inc,0)
  defineintparam("MON",mon,0)
  definebooleanparams("ECho,SQuash,NIn,NOut,Check,SIngle,Tabin,EQuin",bools,0)
  processparameters(cliparam)
  init(echo)
  init(squash)
  init(nin)
  init(nout)
  init(check)
  init(single)
  init(tabin)
  tabin = 0 if bools<0 {equin}
  openinput(instream-2,in3)
  openinput(instream-1,in2)
  openinput(instream,in1)
  openoutput(outstream,out)
end

select output(outstream)
select input(instream)
cycle
  start = cputime
  readin
  printstring("Read in:")
  print time
  newline
  convert
  aim = 999999;  count = 0
  printstring("Implicants:")
  write(sp-dclim,3)
  print time
  newline
  print all if inc#0 and mon&16#0
  reduce1
  printstring("Reduced(1):")
  write(sp-dclim,3)
  printstring(" (nucleus")
  pcount
  printsymbol(')')
  print time
  newline
  print all if inc # 0 and mon&16#0
  if sp # esslim start
    reduce2
    printstring("Reduced(2):")
    write(sp-dclim,3)
    printstring(" (nucleus")
    pcount
    printsymbol(')')
    order if sp # esslim
    print time
    newline
    print all if inc # 0 and mon&16#0
  finish
  monitor(esslim) if mon&2 # 0
  if sp # esslim start
    monitor(sp) if mon&8 # 0
    printstring("Minimised:")
    minimise
  finish
  print all if inc # 0 and mon&1 = 0
  printstring("  Cells used:")
  write(storebound-1-minsep,1)
  print time
  newline
repeat
endofprogram