Here are my notes and links to useful resources on surreals.
Please don’t use this to do any sums for safety critical systems ;-)
This is a helper function:
is_integer <- \(x) x == as.integer(x)is_integer(42)## [1] TRUEis_integer(pi)## [1] FALSEI represent surreals as lists. This is another helper to make them and apply the class “surreal”.
as.surreal <- function(l) {
  res <- l
  
  if(is.null(res) || length(l) == 0)
    res <- nullset
  
  class(res) <- "surreal"
  res
}Rather than sets of surreals, I’m using lists and ignoring duplicates and order in the output…
as.surreal_list <- function(sl) {
  res <- sl
  class(res) <- "surreal_list"
  res
}Some useful predicates:
is.surreal <- function(s)
  class(s) == "surreal"
is.surreal_list <- function(sl)
  class(sl) == "surreal_list"
is.nullset <- function(s) {
  is.surreal(s) && length(s) == 0
}And the main way to construct surreals and lists of surreals:
surreal <- function(l, r) {
  list(l = l,
       r = r) |> as.surreal()
}
surreals <- function(...) {
  res <- list(...) |> unique()
  class(res) <- "surreal_list"
  res
}How to peek into the left or right pair of a surreal. Note that if there’s nothing there to peek at, I just return an empty set.
L <- function(s) {
  stopifnot(class(s) == "surreal")
  
  if (is.null(s) || length(s) == 0)
    nullset
  else
    s$l
}
R <- function(s) {
  stopifnot(class(s) == "surreal")
  
  if (is.null(s) || length(s) == 0)
    nullset
  else
    s$r
}And the empty set. Well, list.
nullset <- list()
class(nullset) <- "surreal"This seems to work… At present it just removes duplicates and nullsets. It could also go through and remove elements in L that are smaller than the largest surreal and elements of R that are larger than the smallest surreal.
simplify_surreals <- function(s) {
  if (is.surreal(s)) {
    if (is.nullset(s))
      nullset
    else
      surreal(simplify_surreals(s |> L()),
              simplify_surreals(s |> R()))
  }
  else if (is.surreal_list(s)) {
    if (length(s) == 0)
      nullset
    else if (length(s) == 1)
      simplify_surreals(s[[1]])
    else {
      # find nulls and zap them
      res <- c()
      for (one_s in s) {
        one_res <- simplify_surreals(one_s)
        if (!is.nullset(one_res))
          res <- c(res, list(one_res))
      }
      res |> unique() |> as.surreal_list()
    }
  }
  else
    stop("No idea what to do with that, sorry")
}This simplifies dyadic numbers, \(n/2^k\).
simplify_dyadic <- \(n, k) {
  stopifnot(is_integer(n))
  stopifnot(is_integer(k))
  stopifnot(k >= 0)
  
  while (k > 0 && n %% 2 == 0) {
    n <- n/2
    k <- k - 1
  }
  
  c(n, k)
}This is Tøndering’s “dali” function that builds a surreal from a dyadic number.
# x = n/2^k
dali <- \(n, k, loud = FALSE) {
  stopifnot(is_integer(n))
  stopifnot(is_integer(k))
  stopifnot(k >= 0)
  
  if (loud) {
    cat("dali called with ")
    cat(n); cat("/"); cat(2^k)
  }
  
  n_old <- n
  k_old <- k
  
  simple <- simplify_dyadic(n,k)
  n <- simple[1]
  k <- simple[2]
  
  if (loud && (n != n_old || k != k_old)) {
    cat(" = "); cat(n); cat("/"); cat(2^k)
  }
  
  if (loud) {
    cat(" = "); cat(n/2^k); cat("\n")
  }
  
  res <- NA
  
  if (n == 0) {
    res <- list(l = nullset, r = nullset)
  }
  else if (k == 0) {
    if (n > 0)
      res <- list(l = dali(n - 1, 0), r = nullset)
    else
      res <- list(l = nullset, r = dali(n + 1, 0))      
  }
  else {
    res <- list(l = dali(n-1, k), r = dali(n+1, k))
  }
  
  class(res) <- "surreal"
  res
}Print surreals:
print.surreal <- function(s) {
  stopifnot(class(s) == "surreal")
  stopifnot(length(s) %in% c(0,2))
  
  if (length(s) == 0) {
    cat("∅")
  }
  else if ((length(s) == 2) &&
           all(names(s) == c("l", "r"))) {
    cat("(")
    print(s |> L())
    cat(" | ")
    print(s |> R())
    cat(")")    
  }
  else
    stop("I don't know how to print that surreal")
}And lists of surreals:
print.surreal_list <- function(surs) {
  stopifnot(class(surs) == "surreal_list")
  
  if (length(surs) == 0)
    cat("∅")
  else {
    i <- 1
    for (s in surs) {
      print(s)
      if (i < length(surs))
        cat(", ")
      i <- i+1
    }
  }
}(In)equalities:
less_equal <- function(x, y) {
  greater_equal(y, x)
}
greater_equal <- function(x, y) {
  if (is.nullset(x) || is.nullset(y))
    FALSE # BEWARE: I don't know why this isn't TRUE...
          # but it seems to work as is 
  else {
    res <- c() 
    if (is.surreal(x |> R()))
      res <- c(res, less_equal(x |> R(), y))
    else
      for (x_R in x |> R())
        res <- c(res, less_equal(x_R, y))
    
    if (is.surreal(y |> L()))
      res <- c(res, less_equal(x, y |> L()))
    else    
      for (y_L in y |> L())
        res <- c(res, less_equal(x, y_L))
    !any(res)
  }
}equal <- function(x,y)
  greater_equal(x,y) && less_equal(x,y)
less <- function(x,y)
  less_equal(x,y) && !equal(x,y)
greater <- function(x,y)
  greater_equal(x,y) && !equal(x,y)Given all the above, addition is relatively painless. You will see I haven’t done multiplication yet.
This can be improved very quickly by removing duplicates (TODO). Also it doesn’t work with sets as inputs. It’s fine for adding dalis.
add <- function(a, b) {
  if (length(a) == 0 || length(b) == 0) {
    nullset
  }
  else {
    surreal(l = surreals(add(a |> L(), b),
                         add(a, b |> L())),
            r = surreals(add(a |> R(), b),
                         add(a, b |> R())))
  }
}And some examples:
add(dali(0,0), dali(0,0))## (∅ | ∅)add(dali(1,0), dali(1,0)) |> simplify_surreals()## (((∅ | ∅) | ∅) | ∅)add(dali(1,0), dali(1,1))## ((∅, (∅ | ∅) | ∅, (∅, (∅ | ∅) | ∅)), ((∅ | ∅), ∅ | ∅) | ∅, ((∅, (∅ | ∅) | ∅), ((∅ | ∅), ∅ | ∅) | ∅))add(dali(1,0), dali(1,1)) |> simplify_surreals()## (((∅ | ∅) | ((∅ | ∅) | ∅)), ((∅ | ∅) | ∅) | (((∅ | ∅) | ∅) | ∅))dali(1,0) # 1## ((∅ | ∅) | ∅)dali(2,0) # 2## (((∅ | ∅) | ∅) | ∅)# 1+1 = 2
add(dali(1,0), dali(1,0)) |> simplify_surreals()## (((∅ | ∅) | ∅) | ∅)Hurrah, so 1+1 = 2. Great.
add(dali(2,0), dali(-2,0)) |> simplify_surreals()## (((∅ | (∅ | (∅ | ∅))) | ((∅ | (∅ | ∅)) | ((∅ | ∅) | ∅))) | (((∅ | (∅ | ∅)) | ((∅ | ∅) | ∅)) | (((∅ | ∅) | ∅) | ∅)))That mess above is equal to zero.
equal(add(dali(2,0), dali(-2,0)), dali(0,0))## [1] TRUEIt’s easy to see as left and right are mirror images of each other.
(((∅ | (∅ | (∅ | ∅))) | ((∅ | (∅ | ∅)) | ((∅ | ∅) | ∅))) | (((∅ | (∅ | ∅)) | ((∅ | ∅) | ∅)) | (((∅ | ∅) | ∅) | ∅)))
raw_sum <- add(dali(2,2), dali(2,2))
simp_sum <- raw_sum |> simplify_surreals()
correct_ans <- dali(1,0)raw_sum## ((∅, (∅ | ∅) | ∅, (∅, (∅ | ∅) | ∅)), ((∅ | ∅), ∅ | ((∅ | ∅), ∅ | ∅), ∅) | ((∅, (∅ | ∅) | ∅, (∅, (∅ | ∅) | ∅)), ((∅ | ∅), ∅ | ∅) | ∅, ((∅, (∅ | ∅) | ∅), ((∅ | ∅), ∅ | ∅) | ∅)), ((∅, (∅ | ∅) | ∅), ((∅ | ∅), ∅ | ((∅ | ∅), ∅ | ∅), ∅) | ((∅, (∅ | ∅) | ∅), ((∅ | ∅), ∅ | ∅) | ∅), ∅))simp_sum## (((∅ | ∅) | ((∅ | ∅) | ∅)) | (((∅ | ∅) | ((∅ | ∅) | ∅)), ((∅ | ∅) | ∅) | (((∅ | ∅) | ∅) | ∅)), (((∅ | ∅) | ∅), ((∅ | ∅) | ((∅ | ∅) | ∅)) | (((∅ | ∅) | ∅) | ∅)))correct_ans## ((∅ | ∅) | ∅)equal(raw_sum, simp_sum)## [1] TRUEequal(simp_sum, correct_ans)## [1] TRUELet’s check whether a putative surreal really is:
legit_surreal <- function(s) {
  !greater_equal(s |> L(), s |> R())
}YES:
legit_surreal(dali(0,1))## [1] TRUENOPE:
legit_surreal(surreal(dali(0,1), dali(0,1)))## [1] FALSEnullset## ∅new_surreals <- function(old_list) {
  cat("Starting with: ")
  print(old_list)
  cat("\n")
  res <- list()
  
  checked <- 0
  legit   <- 0
  
  for (l in old_list)
    for (r in old_list) {
      candidate <- surreal(l, r)
      
      # There must be an easier way that works!
      deja_vu <- (length(c(old_list, list(candidate)) 
                         |> unique()) == length(old_list))
      
      if (!deja_vu) {
        cat("Checking: ")
        print(candidate)
        checked <- checked + 1
  
        if (legit_surreal(candidate)) {
          res <- c(res, list(candidate))
          cat(" - Yes\n")
          legit <- legit + 1
        }
        else
          cat(" - No\n")
      }
    }
  cat("\n")
  cat(legit)
  cat("/")
  cat(checked)
  cat(" were valid\n")
  
  res |> as.surreal_list()
}cat("Let's make some surreal numbers!\n\n")## Let's make some surreal numbers!last_day = 3
so_far <- surreals(nullset)
for (i in 1:(last_day+1)) {
  cat("Day ")
  cat(i-1)
  cat("\n")
  so_far <- c(so_far, new_surreals(so_far)) |> unique() |>
    as.surreal_list()
  cat("\n")
}## Day 0
## Starting with: ∅
## Checking: (∅ | ∅) - Yes
## 
## 1/1 were valid
## 
## Day 1
## Starting with: ∅, (∅ | ∅)
## Checking: (∅ | (∅ | ∅)) - Yes
## Checking: ((∅ | ∅) | ∅) - Yes
## Checking: ((∅ | ∅) | (∅ | ∅)) - No
## 
## 2/3 were valid
## 
## Day 2
## Starting with: ∅, (∅ | ∅), (∅ | (∅ | ∅)), ((∅ | ∅) | ∅)
## Checking: (∅ | (∅ | (∅ | ∅))) - Yes
## Checking: (∅ | ((∅ | ∅) | ∅)) - Yes
## Checking: ((∅ | ∅) | (∅ | ∅)) - No
## Checking: ((∅ | ∅) | (∅ | (∅ | ∅))) - No
## Checking: ((∅ | ∅) | ((∅ | ∅) | ∅)) - Yes
## Checking: ((∅ | (∅ | ∅)) | ∅) - Yes
## Checking: ((∅ | (∅ | ∅)) | (∅ | ∅)) - Yes
## Checking: ((∅ | (∅ | ∅)) | (∅ | (∅ | ∅))) - No
## Checking: ((∅ | (∅ | ∅)) | ((∅ | ∅) | ∅)) - Yes
## Checking: (((∅ | ∅) | ∅) | ∅) - Yes
## Checking: (((∅ | ∅) | ∅) | (∅ | ∅)) - No
## Checking: (((∅ | ∅) | ∅) | (∅ | (∅ | ∅))) - No
## Checking: (((∅ | ∅) | ∅) | ((∅ | ∅) | ∅)) - No
## 
## 7/13 were valid
## 
## Day 3
## Starting with: ∅, (∅ | ∅), (∅ | (∅ | ∅)), ((∅ | ∅) | ∅), (∅ | (∅ | (∅ | ∅))), (∅ | ((∅ | ∅) | ∅)), ((∅ | ∅) | ((∅ | ∅) | ∅)), ((∅ | (∅ | ∅)) | ∅), ((∅ | (∅ | ∅)) | (∅ | ∅)), ((∅ | (∅ | ∅)) | ((∅ | ∅) | ∅)), (((∅ | ∅) | ∅) | ∅)
## Checking: (∅ | (∅ | (∅ | (∅ | ∅)))) - Yes
## Checking: (∅ | (∅ | ((∅ | ∅) | ∅))) - Yes
## Checking: (∅ | ((∅ | ∅) | ((∅ | ∅) | ∅))) - Yes
## Checking: (∅ | ((∅ | (∅ | ∅)) | ∅)) - Yes
## Checking: (∅ | ((∅ | (∅ | ∅)) | (∅ | ∅))) - Yes
## Checking: (∅ | ((∅ | (∅ | ∅)) | ((∅ | ∅) | ∅))) - Yes
## Checking: (∅ | (((∅ | ∅) | ∅) | ∅)) - Yes
## Checking: ((∅ | ∅) | (∅ | ∅)) - No
## Checking: ((∅ | ∅) | (∅ | (∅ | ∅))) - No
## Checking: ((∅ | ∅) | (∅ | (∅ | (∅ | ∅)))) - No
## Checking: ((∅ | ∅) | (∅ | ((∅ | ∅) | ∅))) - No
## Checking: ((∅ | ∅) | ((∅ | ∅) | ((∅ | ∅) | ∅))) - Yes
## Checking: ((∅ | ∅) | ((∅ | (∅ | ∅)) | ∅)) - No
## Checking: ((∅ | ∅) | ((∅ | (∅ | ∅)) | (∅ | ∅))) - No
## Checking: ((∅ | ∅) | ((∅ | (∅ | ∅)) | ((∅ | ∅) | ∅))) - No
## Checking: ((∅ | ∅) | (((∅ | ∅) | ∅) | ∅)) - Yes
## Checking: ((∅ | (∅ | ∅)) | (∅ | (∅ | ∅))) - No
## Checking: ((∅ | (∅ | ∅)) | (∅ | (∅ | (∅ | ∅)))) - No
## Checking: ((∅ | (∅ | ∅)) | (∅ | ((∅ | ∅) | ∅))) - Yes
## Checking: ((∅ | (∅ | ∅)) | ((∅ | ∅) | ((∅ | ∅) | ∅))) - Yes
## Checking: ((∅ | (∅ | ∅)) | ((∅ | (∅ | ∅)) | ∅)) - Yes
## Checking: ((∅ | (∅ | ∅)) | ((∅ | (∅ | ∅)) | (∅ | ∅))) - Yes
## Checking: ((∅ | (∅ | ∅)) | ((∅ | (∅ | ∅)) | ((∅ | ∅) | ∅))) - Yes
## Checking: ((∅ | (∅ | ∅)) | (((∅ | ∅) | ∅) | ∅)) - Yes
## Checking: (((∅ | ∅) | ∅) | (∅ | ∅)) - No
## Checking: (((∅ | ∅) | ∅) | (∅ | (∅ | ∅))) - No
## Checking: (((∅ | ∅) | ∅) | ((∅ | ∅) | ∅)) - No
## Checking: (((∅ | ∅) | ∅) | (∅ | (∅ | (∅ | ∅)))) - No
## Checking: (((∅ | ∅) | ∅) | (∅ | ((∅ | ∅) | ∅))) - No
## Checking: (((∅ | ∅) | ∅) | ((∅ | ∅) | ((∅ | ∅) | ∅))) - No
## Checking: (((∅ | ∅) | ∅) | ((∅ | (∅ | ∅)) | ∅)) - No
## Checking: (((∅ | ∅) | ∅) | ((∅ | (∅ | ∅)) | (∅ | ∅))) - No
## Checking: (((∅ | ∅) | ∅) | ((∅ | (∅ | ∅)) | ((∅ | ∅) | ∅))) - No
## Checking: (((∅ | ∅) | ∅) | (((∅ | ∅) | ∅) | ∅)) - Yes
## Checking: ((∅ | (∅ | (∅ | ∅))) | ∅) - Yes
## Checking: ((∅ | (∅ | (∅ | ∅))) | (∅ | ∅)) - Yes
## Checking: ((∅ | (∅ | (∅ | ∅))) | (∅ | (∅ | ∅))) - Yes
## Checking: ((∅ | (∅ | (∅ | ∅))) | ((∅ | ∅) | ∅)) - Yes
## Checking: ((∅ | (∅ | (∅ | ∅))) | (∅ | (∅ | (∅ | ∅)))) - No
## Checking: ((∅ | (∅ | (∅ | ∅))) | (∅ | ((∅ | ∅) | ∅))) - Yes
## Checking: ((∅ | (∅ | (∅ | ∅))) | ((∅ | ∅) | ((∅ | ∅) | ∅))) - Yes
## Checking: ((∅ | (∅ | (∅ | ∅))) | ((∅ | (∅ | ∅)) | ∅)) - Yes
## Checking: ((∅ | (∅ | (∅ | ∅))) | ((∅ | (∅ | ∅)) | (∅ | ∅))) - Yes
## Checking: ((∅ | (∅ | (∅ | ∅))) | ((∅ | (∅ | ∅)) | ((∅ | ∅) | ∅))) - Yes
## Checking: ((∅ | (∅ | (∅ | ∅))) | (((∅ | ∅) | ∅) | ∅)) - Yes
## Checking: ((∅ | ((∅ | ∅) | ∅)) | ∅) - Yes
## Checking: ((∅ | ((∅ | ∅) | ∅)) | (∅ | ∅)) - No
## Checking: ((∅ | ((∅ | ∅) | ∅)) | (∅ | (∅ | ∅))) - No
## Checking: ((∅ | ((∅ | ∅) | ∅)) | ((∅ | ∅) | ∅)) - Yes
## Checking: ((∅ | ((∅ | ∅) | ∅)) | (∅ | (∅ | (∅ | ∅)))) - No
## Checking: ((∅ | ((∅ | ∅) | ∅)) | (∅ | ((∅ | ∅) | ∅))) - No
## Checking: ((∅ | ((∅ | ∅) | ∅)) | ((∅ | ∅) | ((∅ | ∅) | ∅))) - Yes
## Checking: ((∅ | ((∅ | ∅) | ∅)) | ((∅ | (∅ | ∅)) | ∅)) - No
## Checking: ((∅ | ((∅ | ∅) | ∅)) | ((∅ | (∅ | ∅)) | (∅ | ∅))) - No
## Checking: ((∅ | ((∅ | ∅) | ∅)) | ((∅ | (∅ | ∅)) | ((∅ | ∅) | ∅))) - No
## Checking: ((∅ | ((∅ | ∅) | ∅)) | (((∅ | ∅) | ∅) | ∅)) - Yes
## Checking: (((∅ | ∅) | ((∅ | ∅) | ∅)) | ∅) - Yes
## Checking: (((∅ | ∅) | ((∅ | ∅) | ∅)) | (∅ | ∅)) - No
## Checking: (((∅ | ∅) | ((∅ | ∅) | ∅)) | (∅ | (∅ | ∅))) - No
## Checking: (((∅ | ∅) | ((∅ | ∅) | ∅)) | ((∅ | ∅) | ∅)) - Yes
## Checking: (((∅ | ∅) | ((∅ | ∅) | ∅)) | (∅ | (∅ | (∅ | ∅)))) - No
## Checking: (((∅ | ∅) | ((∅ | ∅) | ∅)) | (∅ | ((∅ | ∅) | ∅))) - No
## Checking: (((∅ | ∅) | ((∅ | ∅) | ∅)) | ((∅ | ∅) | ((∅ | ∅) | ∅))) - No
## Checking: (((∅ | ∅) | ((∅ | ∅) | ∅)) | ((∅ | (∅ | ∅)) | ∅)) - No
## Checking: (((∅ | ∅) | ((∅ | ∅) | ∅)) | ((∅ | (∅ | ∅)) | (∅ | ∅))) - No
## Checking: (((∅ | ∅) | ((∅ | ∅) | ∅)) | ((∅ | (∅ | ∅)) | ((∅ | ∅) | ∅))) - No
## Checking: (((∅ | ∅) | ((∅ | ∅) | ∅)) | (((∅ | ∅) | ∅) | ∅)) - Yes
## Checking: (((∅ | (∅ | ∅)) | ∅) | ∅) - Yes
## Checking: (((∅ | (∅ | ∅)) | ∅) | (∅ | ∅)) - No
## Checking: (((∅ | (∅ | ∅)) | ∅) | (∅ | (∅ | ∅))) - No
## Checking: (((∅ | (∅ | ∅)) | ∅) | ((∅ | ∅) | ∅)) - Yes
## Checking: (((∅ | (∅ | ∅)) | ∅) | (∅ | (∅ | (∅ | ∅)))) - No
## Checking: (((∅ | (∅ | ∅)) | ∅) | (∅ | ((∅ | ∅) | ∅))) - No
## Checking: (((∅ | (∅ | ∅)) | ∅) | ((∅ | ∅) | ((∅ | ∅) | ∅))) - Yes
## Checking: (((∅ | (∅ | ∅)) | ∅) | ((∅ | (∅ | ∅)) | ∅)) - No
## Checking: (((∅ | (∅ | ∅)) | ∅) | ((∅ | (∅ | ∅)) | (∅ | ∅))) - No
## Checking: (((∅ | (∅ | ∅)) | ∅) | ((∅ | (∅ | ∅)) | ((∅ | ∅) | ∅))) - No
## Checking: (((∅ | (∅ | ∅)) | ∅) | (((∅ | ∅) | ∅) | ∅)) - Yes
## Checking: (((∅ | (∅ | ∅)) | (∅ | ∅)) | ∅) - Yes
## Checking: (((∅ | (∅ | ∅)) | (∅ | ∅)) | (∅ | ∅)) - Yes
## Checking: (((∅ | (∅ | ∅)) | (∅ | ∅)) | (∅ | (∅ | ∅))) - No
## Checking: (((∅ | (∅ | ∅)) | (∅ | ∅)) | ((∅ | ∅) | ∅)) - Yes
## Checking: (((∅ | (∅ | ∅)) | (∅ | ∅)) | (∅ | (∅ | (∅ | ∅)))) - No
## Checking: (((∅ | (∅ | ∅)) | (∅ | ∅)) | (∅ | ((∅ | ∅) | ∅))) - Yes
## Checking: (((∅ | (∅ | ∅)) | (∅ | ∅)) | ((∅ | ∅) | ((∅ | ∅) | ∅))) - Yes
## Checking: (((∅ | (∅ | ∅)) | (∅ | ∅)) | ((∅ | (∅ | ∅)) | ∅)) - Yes
## Checking: (((∅ | (∅ | ∅)) | (∅ | ∅)) | ((∅ | (∅ | ∅)) | (∅ | ∅))) - No
## Checking: (((∅ | (∅ | ∅)) | (∅ | ∅)) | ((∅ | (∅ | ∅)) | ((∅ | ∅) | ∅))) - Yes
## Checking: (((∅ | (∅ | ∅)) | (∅ | ∅)) | (((∅ | ∅) | ∅) | ∅)) - Yes
## Checking: (((∅ | (∅ | ∅)) | ((∅ | ∅) | ∅)) | ∅) - Yes
## Checking: (((∅ | (∅ | ∅)) | ((∅ | ∅) | ∅)) | (∅ | ∅)) - No
## Checking: (((∅ | (∅ | ∅)) | ((∅ | ∅) | ∅)) | (∅ | (∅ | ∅))) - No
## Checking: (((∅ | (∅ | ∅)) | ((∅ | ∅) | ∅)) | ((∅ | ∅) | ∅)) - Yes
## Checking: (((∅ | (∅ | ∅)) | ((∅ | ∅) | ∅)) | (∅ | (∅ | (∅ | ∅)))) - No
## Checking: (((∅ | (∅ | ∅)) | ((∅ | ∅) | ∅)) | (∅ | ((∅ | ∅) | ∅))) - No
## Checking: (((∅ | (∅ | ∅)) | ((∅ | ∅) | ∅)) | ((∅ | ∅) | ((∅ | ∅) | ∅))) - Yes
## Checking: (((∅ | (∅ | ∅)) | ((∅ | ∅) | ∅)) | ((∅ | (∅ | ∅)) | ∅)) - No
## Checking: (((∅ | (∅ | ∅)) | ((∅ | ∅) | ∅)) | ((∅ | (∅ | ∅)) | (∅ | ∅))) - No
## Checking: (((∅ | (∅ | ∅)) | ((∅ | ∅) | ∅)) | ((∅ | (∅ | ∅)) | ((∅ | ∅) | ∅))) - No
## Checking: (((∅ | (∅ | ∅)) | ((∅ | ∅) | ∅)) | (((∅ | ∅) | ∅) | ∅)) - Yes
## Checking: ((((∅ | ∅) | ∅) | ∅) | ∅) - Yes
## Checking: ((((∅ | ∅) | ∅) | ∅) | (∅ | ∅)) - No
## Checking: ((((∅ | ∅) | ∅) | ∅) | (∅ | (∅ | ∅))) - No
## Checking: ((((∅ | ∅) | ∅) | ∅) | ((∅ | ∅) | ∅)) - No
## Checking: ((((∅ | ∅) | ∅) | ∅) | (∅ | (∅ | (∅ | ∅)))) - No
## Checking: ((((∅ | ∅) | ∅) | ∅) | (∅ | ((∅ | ∅) | ∅))) - No
## Checking: ((((∅ | ∅) | ∅) | ∅) | ((∅ | ∅) | ((∅ | ∅) | ∅))) - No
## Checking: ((((∅ | ∅) | ∅) | ∅) | ((∅ | (∅ | ∅)) | ∅)) - No
## Checking: ((((∅ | ∅) | ∅) | ∅) | ((∅ | (∅ | ∅)) | (∅ | ∅))) - No
## Checking: ((((∅ | ∅) | ∅) | ∅) | ((∅ | (∅ | ∅)) | ((∅ | ∅) | ∅))) - No
## Checking: ((((∅ | ∅) | ∅) | ∅) | (((∅ | ∅) | ∅) | ∅)) - No
## 
## 50/111 were validcat("By the end of day ")## By the end of daycat(last_day)## 3cat(", we got the following surreals:\n")## , we got the following surreals:for (s in so_far) {
  print(s)
  cat("\n")
}## ∅
## (∅ | ∅)
## (∅ | (∅ | ∅))
## ((∅ | ∅) | ∅)
## (∅ | (∅ | (∅ | ∅)))
## (∅ | ((∅ | ∅) | ∅))
## ((∅ | ∅) | ((∅ | ∅) | ∅))
## ((∅ | (∅ | ∅)) | ∅)
## ((∅ | (∅ | ∅)) | (∅ | ∅))
## ((∅ | (∅ | ∅)) | ((∅ | ∅) | ∅))
## (((∅ | ∅) | ∅) | ∅)
## (∅ | (∅ | (∅ | (∅ | ∅))))
## (∅ | (∅ | ((∅ | ∅) | ∅)))
## (∅ | ((∅ | ∅) | ((∅ | ∅) | ∅)))
## (∅ | ((∅ | (∅ | ∅)) | ∅))
## (∅ | ((∅ | (∅ | ∅)) | (∅ | ∅)))
## (∅ | ((∅ | (∅ | ∅)) | ((∅ | ∅) | ∅)))
## (∅ | (((∅ | ∅) | ∅) | ∅))
## ((∅ | ∅) | ((∅ | ∅) | ((∅ | ∅) | ∅)))
## ((∅ | ∅) | (((∅ | ∅) | ∅) | ∅))
## ((∅ | (∅ | ∅)) | (∅ | ((∅ | ∅) | ∅)))
## ((∅ | (∅ | ∅)) | ((∅ | ∅) | ((∅ | ∅) | ∅)))
## ((∅ | (∅ | ∅)) | ((∅ | (∅ | ∅)) | ∅))
## ((∅ | (∅ | ∅)) | ((∅ | (∅ | ∅)) | (∅ | ∅)))
## ((∅ | (∅ | ∅)) | ((∅ | (∅ | ∅)) | ((∅ | ∅) | ∅)))
## ((∅ | (∅ | ∅)) | (((∅ | ∅) | ∅) | ∅))
## (((∅ | ∅) | ∅) | (((∅ | ∅) | ∅) | ∅))
## ((∅ | (∅ | (∅ | ∅))) | ∅)
## ((∅ | (∅ | (∅ | ∅))) | (∅ | ∅))
## ((∅ | (∅ | (∅ | ∅))) | (∅ | (∅ | ∅)))
## ((∅ | (∅ | (∅ | ∅))) | ((∅ | ∅) | ∅))
## ((∅ | (∅ | (∅ | ∅))) | (∅ | ((∅ | ∅) | ∅)))
## ((∅ | (∅ | (∅ | ∅))) | ((∅ | ∅) | ((∅ | ∅) | ∅)))
## ((∅ | (∅ | (∅ | ∅))) | ((∅ | (∅ | ∅)) | ∅))
## ((∅ | (∅ | (∅ | ∅))) | ((∅ | (∅ | ∅)) | (∅ | ∅)))
## ((∅ | (∅ | (∅ | ∅))) | ((∅ | (∅ | ∅)) | ((∅ | ∅) | ∅)))
## ((∅ | (∅ | (∅ | ∅))) | (((∅ | ∅) | ∅) | ∅))
## ((∅ | ((∅ | ∅) | ∅)) | ∅)
## ((∅ | ((∅ | ∅) | ∅)) | ((∅ | ∅) | ∅))
## ((∅ | ((∅ | ∅) | ∅)) | ((∅ | ∅) | ((∅ | ∅) | ∅)))
## ((∅ | ((∅ | ∅) | ∅)) | (((∅ | ∅) | ∅) | ∅))
## (((∅ | ∅) | ((∅ | ∅) | ∅)) | ∅)
## (((∅ | ∅) | ((∅ | ∅) | ∅)) | ((∅ | ∅) | ∅))
## (((∅ | ∅) | ((∅ | ∅) | ∅)) | (((∅ | ∅) | ∅) | ∅))
## (((∅ | (∅ | ∅)) | ∅) | ∅)
## (((∅ | (∅ | ∅)) | ∅) | ((∅ | ∅) | ∅))
## (((∅ | (∅ | ∅)) | ∅) | ((∅ | ∅) | ((∅ | ∅) | ∅)))
## (((∅ | (∅ | ∅)) | ∅) | (((∅ | ∅) | ∅) | ∅))
## (((∅ | (∅ | ∅)) | (∅ | ∅)) | ∅)
## (((∅ | (∅ | ∅)) | (∅ | ∅)) | (∅ | ∅))
## (((∅ | (∅ | ∅)) | (∅ | ∅)) | ((∅ | ∅) | ∅))
## (((∅ | (∅ | ∅)) | (∅ | ∅)) | (∅ | ((∅ | ∅) | ∅)))
## (((∅ | (∅ | ∅)) | (∅ | ∅)) | ((∅ | ∅) | ((∅ | ∅) | ∅)))
## (((∅ | (∅ | ∅)) | (∅ | ∅)) | ((∅ | (∅ | ∅)) | ∅))
## (((∅ | (∅ | ∅)) | (∅ | ∅)) | ((∅ | (∅ | ∅)) | ((∅ | ∅) | ∅)))
## (((∅ | (∅ | ∅)) | (∅ | ∅)) | (((∅ | ∅) | ∅) | ∅))
## (((∅ | (∅ | ∅)) | ((∅ | ∅) | ∅)) | ∅)
## (((∅ | (∅ | ∅)) | ((∅ | ∅) | ∅)) | ((∅ | ∅) | ∅))
## (((∅ | (∅ | ∅)) | ((∅ | ∅) | ∅)) | ((∅ | ∅) | ((∅ | ∅) | ∅)))
## (((∅ | (∅ | ∅)) | ((∅ | ∅) | ∅)) | (((∅ | ∅) | ∅) | ∅))
## ((((∅ | ∅) | ∅) | ∅) | ∅)This is fun and unexpected:
equal(surreal(dali(3,0), dali(17,0)), dali(10,0))## [1] FALSEequal(surreal(dali(3,0), dali(17,0)), dali(4,0))## [1] TRUE