Hi Charles,
It seems that maybe, _maybe_, SimpleList could indeed be defined with something like this:
library(S4Vectors)
setClass("SimpleList2", contains=c("List", "list"))
setMethod("parallel_slot_names", "SimpleList2", function(x) c(".Data", callNextMethod()))
setMethod("as.list", "SimpleList2", function(x) setNames(x@.Data, names(x)))
Then:
x <- new("SimpleList2", list(a=11:13, b=22:25, c=NULL, d="A"))
length(x)
# [1] 4
names(x)
# [1] "a" "b" "c" "d"
x
# SimpleList2 of length 4
# names(4): a b c d
validObject(x)
# [1] TRUE
as.list(x)
# $a
# [1] 11 12 13
#
# $b
# [1] 22 23 24 25
#
# $c
# NULL
#
# $d
# [1] "A"
unlist(x)
# a a a b b b b d
# "11" "12" "13" "22" "23" "24" "25" "A"
x[[2]]
# [1] 22 23 24 25
mcols(x)$score <- runif(4)
mcols(x)
# DataFrame with 4 rows and 1 column
# score
# <numeric>
# a 0.1695619
# b 0.0302325
# c 0.9856251
# d 0.1155053
purrr::map(x, rev)
# $a
# [1] 13 12 11
#
# $b
# [1] 25 24 23 22
#
# $c
# NULL
#
# $d
# [1] "A"
So maybe we should do this.
However, this is NOT a trivial change. It's actually a very disruptive one as it will modify the internal representation of all SimpleList objects and derivatives (this includes DFrame objects). This means that all these objects will need to be updated and re-serialized. I already did this about one month ago for thousands of DataFrame objects when DataFrame became virtual, not fun!
I just opened an issue on GitHub where we can discuss this further.
Note that SimpleList and its place under the List class hierarchy has a long and complicated history. It started in 2008 when Michael added the TypedList class to the IRanges package (commit 45caa3478fbfd2e5d2f4196326f6a99525659f45). At the time its definition was:
## Wrapper around a list that ensures all elements extend from a certain type
setClass("TypedList",
representation(
elements="list", # a list of R objects
NAMES="characterORNULL" # R doesn't like @names !!
),
prototype(
elements=list(),
NAMES=NULL
),
contains = "VIRTUAL"
)
Then over the 2 or 3 following years it evolved to become what the SimpleList class is today.
I don't know for sure why TypedList was not made a subclass of list when it was introduced. I'm sure it was considered but I suspect that it was discarded because at the time the idea was to support a well-defined API, something that's harder to achieve with S4 objects that derive from standard S3 types. Maybe Michael remembers.
Best,
H.