view src/may/matrix.yeti @ 496:4b85578159e1

Round on printout
author Chris Cannam
date Tue, 19 Nov 2013 14:37:39 +0000
parents 120a2dc3d93b
children 295b66046da3
line wrap: on
line source

/**
 * Matrices. A matrix is a two-dimensional (NxM) container of
 * double-precision floating point values.
 *
 * A matrix may be dense or sparse.
 * 
 * A dense matrix (the default) is just a series of vectors, making up
 * the matrix "grid". The values may be stored in either column-major
 * order, in which case the series consists of one vector for each
 * column in the matrix, or row-major order, in which case the series
 * consists of one vector for each row. The default is column-major.
 * 
 * A sparse matrix has a more complex representation in which only the
 * non-zero values are stored. This is typically used for matrices
 * containing sparse data, that is, data in which most of the values
 * are zero: using a sparse representation is more efficient than a
 * dense one (in both time and memory) if the matrix is very large but
 * contains a relatively low proportion of non-zero values. Like dense
 * matrices, sparse ones may be column-major or row-major.
 * 
 * The choice of dense or sparse, row- or column-major is a question
 * of efficiency alone. All functions in this module should return the
 * same results regardless of how the matrices they operate on are
 * represented. However, differences in performance can be very large
 * and it is often worth converting matrices to a different storage
 * format if you know they can be more efficiently manipulated that
 * way. For example, multiplying two matrices is fastest if the first
 * is in column-major and the second in row-major order.
 * 
 * Use the isRowMajor? and isSparse? functions to query the storage
 * format of a matrix; use the flipped function to convert between
 * column-major and row-major storage; and use toSparse and toDense to
 * convert between sparse and dense storage.
 *
 * Note that the matrix representation does not take into account
 * different forms of zero-width or zero-height matrix. All matrices
 * of zero width or height are equal to each other, and all are equal
 * to the zero-sized matrix.
 */

module may.matrix;

vec = load may.vector;
mm = load may.mathmisc;

typedef opaque matrix_t =
    DenseRows array<vec.vector_t> | // array of rows
    DenseCols array<vec.vector_t> | // array of columns
    SparseCSR {
        values is vec.vector_t,
        indices is array<number>, // column index of each value
        pointers is array<number>, // offset of first value in each row
        extent is number // max possible index + 1, i.e. number of columns
        } |
    SparseCSC {
        values is vec.vector_t,
        indices is array<number>, // row index of each value
        pointers is array<number>, // offset of first value in each column
        extent is number // max pointers index + 1, i.e. number of rows
        };

();

width m = 
    case m of
    DenseRows r:
        if not empty? r then vec.length r[0] else 0 fi;
    DenseCols c:
        length c;
    SparseCSR { values, indices, pointers, extent }:
        extent;
    SparseCSC { values, indices, pointers, extent }:
        (length pointers) - 1;
    esac;

height m =
    case m of
    DenseRows r:
        length r;
    DenseCols c:
        if not empty? c then vec.length c[0] else 0 fi;
    SparseCSR { values, indices, pointers, extent }:
        (length pointers) - 1;
    SparseCSC { values, indices, pointers, extent }:
        extent;
    esac;

size m = { rows = height m, columns = width m };

nonZeroValues m =
   (nz d =
        sum
           (map do v:
                sum (map do n: if n == 0 then 0 else 1 fi done (vec.list v))
                done d);
    case m of 
    DenseRows d: nz d;
    DenseCols d: nz d;
    SparseCSR d: vec.length d.values;
    SparseCSC d: vec.length d.values;
    esac);

density m =
   ({ rows, columns } = size m;
    cells = rows * columns;
    (nonZeroValues m) / cells);

sparseSlice n d =
   (start = d.pointers[n];
    end = d.pointers[n+1];
    { 
        values = vec.slice d.values start end,
        indices = slice d.indices start end,
    });

nonEmptySlices d =
   (ne = array [];
    for [0..length d.pointers - 2] do i:
        if d.pointers[i] != d.pointers[i+1] then
            push ne i
        fi
    done;
    ne);

fromSlice n m d =
   (slice = sparseSlice n d;
    var v = 0;
    for [0..length slice.indices - 1] do i:
        if slice.indices[i] == m then
            v := vec.at slice.values i;
        fi
    done;
    v);

filledSlice n d =
   (slice = sparseSlice n d;
    dslice = new double[d.extent];
    for [0..length slice.indices - 1] do i:
        dslice[slice.indices[i]] := vec.at slice.values i;
    done;
    vec.vector dslice);

at' m row col =
    case m of
    DenseRows rows: r = rows[row]; vec.at r col;
    DenseCols cols: c = cols[col]; vec.at c row;
    SparseCSR data: fromSlice row col data;
    SparseCSC data: fromSlice col row data;
    esac;

//!!! better as getXx or just xx?

getColumn j m =
    case m of
    DenseCols cols: cols[j];
    SparseCSC data: filledSlice j data;
    _: vec.fromList (map do i: at' m i j done [0..height m - 1]);
    esac;

getRow i m =
    case m of
    DenseRows rows: rows[i];
    SparseCSR data: filledSlice i data; 
    _: vec.fromList (map do j: at' m i j done [0..width m - 1]);
    esac;

getDiagonal k m =
   (ioff = if k < 0 then -k else 0 fi;
    joff = if k > 0 then  k else 0 fi;
    n = min (width m - joff) (height m - ioff);
    vec.fromList (map do i: at' m (i + ioff) (i + joff) done [0..n - 1]));

asRows m =
    map do i: getRow i m done [0 .. (height m) - 1];

asColumns m =
    map do i: getColumn i m done [0 .. (width m) - 1];

isRowMajor? m =
    case m of
    DenseRows _: true;
    DenseCols _: false;
    SparseCSR _: true;
    SparseCSC _: false;
    esac;

isSparse? m =
    case m of
    DenseRows _: false;
    DenseCols _: false;
    SparseCSR _: true;
    SparseCSC _: true;
    esac;

typeOf m =
    if isRowMajor? m then RowMajor ()
    else ColumnMajor ()
    fi;

flippedTypeOf m =
    if isRowMajor? m then ColumnMajor ()
    else RowMajor ()
    fi;

newColumnMajorStorage { rows, columns } = 
    if rows < 1 then array []
    else array (map \(vec.zeros rows) [1..columns])
    fi;

zeroMatrix { rows, columns } = 
    DenseCols (newColumnMajorStorage { rows, columns });

zeroMatrixWithTypeOf m { rows, columns } = 
    if isRowMajor? m then
        DenseRows (newColumnMajorStorage { rows = columns, columns = rows });
    else
        DenseCols (newColumnMajorStorage { rows, columns });
    fi;

zeroSizeMatrix () = zeroMatrix { rows = 0, columns = 0 };

empty?' m = (width m == 0 or height m == 0);

generate f { rows, columns } =
    if rows < 1 or columns < 1 then zeroSizeMatrix ()
    else
        m = array (map \(new double[rows]) [1..columns]);
        for [0..columns-1] do col:
            for [0..rows-1] do row:
                m[col][row] := f row col;
            done;
        done;
        DenseCols (array (map vec.vector m))
    fi;

swapij =
    map do { i, j, v }: { i = j, j = i, v } done;

//!!! should use { row = , column = , value = } instead of i, j, v?
enumerateSparse m =
   (enumerate { values, indices, pointers } =
        concat
           (map do i:
                start = pointers[i];
                end = pointers[i+1];
                map2 do j v: { i, j, v } done 
                    (slice indices start end)
                    (vec.list (vec.slice values start end))
                done [0..length pointers - 2]);
    case m of
    SparseCSC d: swapij (enumerate d);
    SparseCSR d: enumerate d;
     _: [];
    esac);

enumerateDense m =
   (enumerate d =
        concat
           (map do i:
                vv = d[i];
                map2 do j v: { i, j, v } done
                    [0..vec.length vv - 1]
                    (vec.list vv);
                done [0..length d - 1]);
    case m of
    DenseCols c: swapij (enumerate c);
    DenseRows r: enumerate r;
     _: [];
    esac);

enumerate m =
    if isSparse? m then enumerateSparse m else enumerateDense m fi;

// Make a sparse matrix from entries whose i, j values are known to be
// within range
makeSparse type size data =
   (isRow = case type of RowMajor (): true; ColumnMajor (): false esac;
    ordered = 
        sortBy do a b:
            if a.maj == b.maj then a.min < b.min else a.maj < b.maj fi
        done
           (map
                if isRow then
                    do { i, j, v }: { maj = i, min = j, v } done;
                else
                    do { i, j, v }: { maj = j, min = i, v } done;
                fi
               (filter do d: d.v != 0 done data));
    tagger = if isRow then SparseCSR else SparseCSC fi;
    majorSize = if isRow then size.rows else size.columns fi;
    minorSize = if isRow then size.columns else size.rows fi;
    pointers = array [0];
    setArrayCapacity pointers (size.rows + 1);
    fillPointers n i data =
        if n < majorSize then
            case data of
            d::rest:
               (for [n..d-1] \(push pointers i);
                fillPointers d (i+1) rest);
             _:
                for [n..majorSize-1] \(push pointers i);
            esac;
        fi;
    fillPointers 0 0 (map (.maj) ordered);
    tagger {
        values = vec.fromList (map (.v) ordered),
        indices = array (map (.min) ordered),
        pointers,
        extent = minorSize,
    });

// Make a sparse matrix from entries that may contain out-of-range
// cells which need to be filtered out. This is the public API for
// makeSparse and is also used to discard out-of-range cells from
// resizedTo.
//!!! doc: i is row number, j is column number (throughout, for sparse stuff). Would calling them row/column be better?
newSparseMatrix type size data =
    makeSparse type size
       (filter
            do { i, j, v }:
                i == int i and i >= 0 and i < size.rows and 
                j == int j and j >= 0 and j < size.columns
            done data);

toSparse m =
    if isSparse? m then m
    else
        makeSparse (typeOf m) (size m) (enumerateDense m);
    fi;

toDense m =
    if not (isSparse? m) then m
    elif isRowMajor? m then
        DenseRows (array (map do row: getRow row m done [0..height m - 1]));
    else
        DenseCols (array (map do col: getColumn col m done [0..width m - 1]));
    fi;

constMatrix n = generate do row col: n done;
randomMatrix = generate do row col: Math#random() done;
identityMatrix = constMatrix 1;

transposed m =
    case m of
    DenseRows d: DenseCols d;
    DenseCols d: DenseRows d;
    SparseCSR d: SparseCSC d;
    SparseCSC d: SparseCSR d;
    esac;

flipped m =
    if isSparse? m then
        makeSparse (flippedTypeOf m) (size m) (enumerateSparse m)
    else
        if isRowMajor? m then
            generate do row col: at' m row col done (size m);
        else
            transposed
               (generate do row col: at' m col row done
                { rows = (width m), columns = (height m) });
        fi
    fi;

toRowMajor m =
    if isRowMajor? m then m else flipped m fi;

toColumnMajor m =
    if not isRowMajor? m then m else flipped m fi;

equal'' comparator vecComparator m1 m2 =
    // Prerequisite: m1 and m2 have same sparse-p and storage order
   (compareVecLists vv1 vv2 = all id (map2 vecComparator vv1 vv2);
    compareSparse d1 d2 =
        d1.extent == d2.extent and
        vecComparator d1.values d2.values and
        d1.indices == d2.indices and
        d1.pointers == d2.pointers;
    case m1 of
    DenseRows d1:
        case m2 of DenseRows d2: compareVecLists d1 d2; _: false; esac;
    DenseCols d1:
        case m2 of DenseCols d2: compareVecLists d1 d2; _: false; esac;
    SparseCSR d1:
        case m2 of SparseCSR d2: compareSparse d1 d2; _: false; esac;
    SparseCSC d1:
        case m2 of SparseCSC d2: compareSparse d1 d2; _: false; esac;
    esac);

equal' comparator vecComparator m1 m2 =
    if empty?' m1 and empty?' m2 then
        true
    elif size m1 != size m2 then 
        false
    elif isRowMajor? m1 != isRowMajor? m2 then
        equal' comparator vecComparator (flipped m1) m2;
    elif isSparse? m1 != isSparse? m2 then
        if isSparse? m1 then
            equal' comparator vecComparator m1 (toSparse m2)
        else
            equal' comparator vecComparator (toSparse m1) m2
        fi
    else
        equal'' comparator vecComparator m1 m2
    fi;

// Compare matrices using the given comparator for individual cells.
// Note that matrices with different storage order but the same
// contents are equal, although comparing them is slow.
//!!! Document the fact that sparse matrices can only be equal if they
// have the same set of non-zero cells (regardless of comparator used)
equalUnder comparator =
    equal' comparator (vec.equalUnder comparator);

equal =
    equal' (==) vec.equal;

newMatrix type data = //!!! NB does not copy data
   (tagger = case type of RowMajor (): DenseRows; ColumnMajor (): DenseCols esac;
    if empty? data or vec.empty? (head data)
    then zeroSizeMatrix ()
    else tagger (array data)
    fi);

newRowVector data = //!!! NB does not copy data
    DenseRows (array [data]);

newColumnVector data = //!!! NB does not copy data
    DenseCols (array [data]);

denseLinearOp op m1 m2 =
    if isRowMajor? m1 then
        newMatrix (typeOf m1) 
           (map2 do c1 c2: op c1 c2 done (asRows m1) (asRows m2));
    else
        newMatrix (typeOf m1) 
           (map2 do c1 c2: op c1 c2 done (asColumns m1) (asColumns m2));
    fi;

sparseSumOrDifference op m1 m2 =
   (h = [:];
    for (enumerate m1) do { i, j, v }:
        if not (i in h) then h[i] := [:] fi;
        h[i][j] := v;
    done;
    for (enumerate m2) do { i, j, v }:
        if not (i in h) then h[i] := [:] fi;
        if j in h[i] then h[i][j] := op h[i][j] v;
        else h[i][j] := op 0 v;
        fi;
    done;
    entries = concat
       (map do i:
            kk = keys h[i];
            map2 do j v: { i, j, v } done kk (map (at h[i]) kk)
            done (keys h));
    makeSparse (typeOf m1) (size m1) entries);

sum' m1 m2 =
    if (size m1) != (size m2)
    then failWith "Matrices are not the same size: \(size m1), \(size m2)";
    elif isSparse? m1 and isSparse? m2 then
        sparseSumOrDifference (+) m1 m2;
    else
        add2 v1 v2 = vec.add [v1,v2];
        denseLinearOp add2 m1 m2;
    fi;

difference m1 m2 =
    if (size m1) != (size m2)
    then failWith "Matrices are not the same size: \(size m1), \(size m2)";
    elif isSparse? m1 and isSparse? m2 then
        sparseSumOrDifference (-) m1 m2;
    else
        denseLinearOp vec.subtract m1 m2;
    fi;

scaled factor m =
    if isSparse? m then
        makeSparse (typeOf m) (size m)
           (map do { i, j, v }: { i, j, v = factor * v } done (enumerate m))
    elif isRowMajor? m then
        newMatrix (typeOf m) (map (vec.scaled factor) (asRows m));
    else
        newMatrix (typeOf m) (map (vec.scaled factor) (asColumns m));
    fi;

abs' m =
    if isSparse? m then
        makeSparse (typeOf m) (size m)
           (map do { i, j, v }: { i, j, v = abs v } done (enumerate m))
    elif isRowMajor? m then
        newMatrix (typeOf m) (map vec.abs (asRows m));
    else
        newMatrix (typeOf m) (map vec.abs (asColumns m));
    fi;

negative m =
    if isSparse? m then
        makeSparse (typeOf m) (size m)
           (map do { i, j, v }: { i, j, v = (-v) } done (enumerate m))
    elif isRowMajor? m then
        newMatrix (typeOf m) (map vec.negative (asRows m));
    else
        newMatrix (typeOf m) (map vec.negative (asColumns m));
    fi;

//!!! doc: filter by predicate, always returns sparse matrix
filter' f m =
    makeSparse (typeOf m) (size m)
       (map do { i, j, v }: { i, j, v = if f v then v else 0 fi } done
           (enumerate m));

any' f m =
    any f (map (.v) (enumerate m));

all' f m =
    all f (map (.v) (enumerate m));

sparseProductLeft size m1 m2 =
   ({ values, indices, pointers } = case m1 of
         SparseCSR d: d;
         SparseCSC d: d;
         _: failWith "sparseProductLeft called for non-sparse m1";
         esac;
    rows = isRowMajor? m1;
    data = array (map \(new double[size.rows]) [1..size.columns]);
    for [0..size.columns - 1] do j':
        c = getColumn j' m2;
        var p = 0;
        for [0..length indices - 1] do ix:
            ix == pointers[p+1] loop (p := p + 1);
            i = if rows then p else indices[ix] fi;
            j = if rows then indices[ix] else p fi;
            data[j'][i] := data[j'][i] + (vec.at values ix) * (vec.at c j);
        done;
    done;
    DenseCols (array (map vec.vector (list data))));

sparseProductRight size m1 m2 =
   ({ values, indices, pointers } = case m2 of
         SparseCSR d: d;
         SparseCSC d: d;
         _: failWith "sparseProductLeft called for non-sparse m1";
         esac;
    rows = isRowMajor? m2;
    data = array (map \(new double[size.columns]) [1..size.rows]);
    for [0..size.rows - 1] do i':
        r = getRow i' m1;
        var p = 0;
        for [0..length indices - 1] do ix:
            ix == pointers[p+1] loop (p := p + 1);
            i = if rows then p else indices[ix] fi;
            j = if rows then indices[ix] else p fi;
            data[i'][j] := data[i'][j] + (vec.at values ix) * (vec.at r i);
        done;
    done;
    DenseRows (array (map vec.vector (list data))));

sparseProduct size m1 m2 =
    case m2 of
    SparseCSC d:
       ({ values, indices, pointers } = case m1 of
            SparseCSR d1: d1;
            SparseCSC d1: d1;
            _: failWith "sparseProduct called for non-sparse matrices";
            esac;
        rows = isRowMajor? m1;
        var p = 0;
        pindices = new int[length indices];
        for [0..length indices - 1] do ix:
            ix == pointers[p+1] loop (p := p + 1);
            pindices[ix] := p;
        done;
        entries =
           (map do j':
                cs = sparseSlice j' d;
                hin = mapIntoHash
                   (at cs.indices) (vec.at cs.values)
                   [0..length cs.indices - 1];
                hout = [:];
                for [0..length indices - 1] do ix:
                    i = if rows then pindices[ix] else indices[ix] fi;
                    j = if rows then indices[ix] else pindices[ix] fi;
                    if j in hin then
                        p = (vec.at values ix) * hin[j];
                        hout[i] := p + (if i in hout then hout[i] else 0 fi);
                    fi;
                done;
                map do i:
                    { i, j = j', v = hout[i] }
                done (keys hout);
            done (nonEmptySlices d));
        makeSparse (ColumnMajor ()) size (concat entries));
    SparseCSR _:
        sparseProduct size m1 (flipped m2);
     _: failWith "sparseProduct called for non-sparse matrices";
    esac;

denseProduct size m1 m2 =
   (data = array (map \(new double[size.rows]) [1..size.columns]);
    for [0..size.rows - 1] do i:
        row = getRow i m1;
        for [0..size.columns - 1] do j:
            data[j][i] := vec.sum (vec.multiply row (getColumn j m2));
        done;
    done;
    DenseCols (array (map vec.vector (list data))));

product m1 m2 =
    if (size m1).columns != (size m2).rows
    then failWith "Matrix dimensions incompatible: \(size m1), \(size m2) (\((size m1).columns) != \((size m2).rows))";
    else 
        size = { rows = (size m1).rows, columns = (size m2).columns };
        if isSparse? m1 then
            if isSparse? m2 then
                sparseProduct size m1 m2
            else
                sparseProductLeft size m1 m2
            fi
        elif isSparse? m2 then
            sparseProductRight size m1 m2
        else
            denseProduct size m1 m2
        fi;
    fi;

entryWiseProduct m1 m2 = // or element-wise, or Hadamard product
//!!! todo: faster, sparse version, unit tests
    if (size m1) != (size m2)
    then failWith "Matrices are not the same size: \(size m1), \(size m2)";
    else generate do row col: at' m1 row col * at' m2 row col done (size m1);
    fi;

concatAgainstGrain tagger getter counter mm =
   (n = counter (size (head mm));
    tagger (array
       (map do i:
           vec.concat (map (getter i) mm)
           done [0..n-1])));

concatWithGrain tagger getter counter mm =
    tagger (array
       (concat
           (map do m:
               n = counter (size m);
               map do i: getter i m done [0..n-1]
               done mm)));

sparseConcat direction first mm =
   (dimension d f = if direction == d then sum (map f mm) else f first fi;
    rows = dimension (Vertical ()) height;
    columns = dimension (Horizontal ()) width;
    entries ioff joff ui uj mm acc =
        case mm of 
        m::rest:
            entries
               (ioff + ui * height m)
               (joff + uj * width m)
                ui uj rest
               ((map do { i, j, v }: { i = i + ioff, j = j + joff, v }
                 done (enumerate m)) ++ acc);
         _: acc;
        esac;
    makeSparse (typeOf first) { rows, columns }
        if direction == Vertical () then entries 0 0 1 0 mm []
        else entries 0 0 0 1 mm [] fi);

checkDimensions counter first mm =
   (n = counter (size first);
    if not (all id (map do m: counter (size m) == n done mm)) then
        failWith "Matrix dimensions incompatible for concat (found \(map do m: counter (size m) done mm) not all of which are \(n))";
    fi);

concatHorizontal' mm = //!!! doc: storage order is taken from first matrix in sequence; concat is obviously not lazy (unlike std module)
    case mm of
    [m]: m;
    first::rest:
       (checkDimensions (.rows) first mm;
        if all isSparse? mm then
            sparseConcat (Horizontal ()) first mm
        else
            row = isRowMajor? first;
            // horizontal, row-major: against grain with rows
            // horizontal, col-major: with grain with cols
            if row then concatAgainstGrain DenseRows getRow (.rows) mm;
            else concatWithGrain DenseCols getColumn (.columns) mm;
            fi;
        fi);
     _: zeroSizeMatrix ();
    esac;

concatVertical' mm = //!!! doc: storage order is taken from first matrix in sequence; concat is obviously not lazy (unlike std module)
    case mm of
    [m]: m;
    first::rest:
       (checkDimensions (.columns) first mm;
        if all isSparse? mm then
            sparseConcat (Vertical ()) first mm
        else
            row = isRowMajor? first;
            // vertical, row-major: with grain with rows
            // vertical, col-major: against grain with cols
            if row then concatWithGrain DenseRows getRow (.rows) mm;
            else concatAgainstGrain DenseCols getColumn (.columns) mm;
            fi;
        fi);
     _: zeroSizeMatrix ();
    esac;

//!!! doc this filter -- zero-size elts are ignored
concatHorizontal mm =
    concatHorizontal' (filter do mat: not (empty?' mat) done mm);

//!!! doc this filter -- zero-size elts are ignored
concatVertical mm =
    concatVertical' (filter do mat: not (empty?' mat) done mm);

//!!! next two v. clumsy

//!!! doc note: argument order chosen for consistency with std module slice
//!!! NB always returns dense matrix, should have sparse version
rowSlice m start end = //!!! doc: storage order same as input
    if start < 0 then rowSlice m 0 end
    elif start > height m then rowSlice m (height m) end
    else
        if end < start then rowSlice m start start
        elif end > height m then rowSlice m start (height m)
        else
            if isRowMajor? m then
                DenseRows (array (map ((flip getRow) m) [start .. end - 1]))
            else 
                DenseCols (array (map do v: vec.slice v start end done (asColumns m)))
            fi;
        fi;
    fi;

//!!! doc note: argument order chosen for consistency with std module slice
//!!! NB always returns dense matrix, should have sparse version
columnSlice m start end = //!!! doc: storage order same as input
    if start < 0 then columnSlice m 0 end
    elif start > width m then columnSlice m (width m) end
    else
        if end < start then columnSlice m start start
        elif end > width m then columnSlice m start (width m)
        else
            if not isRowMajor? m then
                DenseCols (array (map ((flip getColumn) m) [start .. end - 1]))
            else 
                DenseRows (array (map do v: vec.slice v start end done (asRows m)))
            fi;
        fi;
    fi;

resizedTo newsize m =
   (if newsize == (size m) then
        m
    elif isSparse? m then
        // don't call makeSparse directly: want to discard
        // out-of-range cells
        newSparseMatrix (typeOf m) newsize (enumerateSparse m)
    elif (height m) == 0 or (width m) == 0 then
        zeroMatrixWithTypeOf m newsize;
    else
        growrows = newsize.rows - (height m);
        growcols = newsize.columns - (width m);
        rowm = isRowMajor? m;
        resizedTo newsize
            if rowm and growrows < 0 then
                rowSlice m 0 newsize.rows
            elif (not rowm) and growcols < 0 then 
                columnSlice m 0 newsize.columns
            elif growrows < 0 then 
                rowSlice m 0 newsize.rows
            elif growcols < 0 then 
                columnSlice m 0 newsize.columns
            else
                if growrows > 0 then
                    concatVertical
                       [m, zeroMatrixWithTypeOf m ((size m) with { rows = growrows })]
                else
                    concatHorizontal
                       [m, zeroMatrixWithTypeOf m ((size m) with { columns = growcols })]
                fi
            fi
    fi);

minValue m =
    if empty?' m then 0
    else 
        minv ll = fold min (head ll) (tail ll);
        minv (map (.v) (enumerate m));
    fi;

maxValue m =
    if empty?' m then 0
    else 
        maxv ll = fold max (head ll) (tail ll);
        maxv (map (.v) (enumerate m));
    fi;

format m =
    strJoin "\n"
       (chunk = 8;
        map do b:
            c0 = b * chunk;
            c1 = b * chunk + chunk - 1;
            c1 = if c1 > width m then width m else c1 fi;
            [ "\nColumns \(c0) to \(c1)\n",
              (map do row:
                   map do v:
                       n = mm.round (v * 10000);
                       strPad ' ' 10 "\(n / 10000)";
                   done (vec.list row);
               done (asRows (columnSlice m c0 (c1 + 1))) |> concat |> strJoin "")
            ];
        done [0..width m / chunk - 1] |> concat);

print' = print . format;

//!!! todo: look at all occurrences of matrix (and complexmatrix)
// construction and make sure we have good apis for those use cases.
// in particular, constructing from literal data (list<list<number>>)
// is much too hard at the moment.

{
    size,
    width,
    height,
    density,
    nonZeroValues,
    at = at',
    getColumn,
    getRow,
    getDiagonal,
    isRowMajor?,
    isSparse?,
    generate,
    constMatrix,
    randomMatrix,
    zeroMatrix,
    identityMatrix,
    zeroSizeMatrix,
    empty? = empty?',
    equal, //!!! if empty is empty?, why is equal not equal? ?
    equalUnder,
    transposed,
    flipped,
    toRowMajor,
    toColumnMajor,
    toSparse,
    toDense,
    scaled,
    resizedTo,
    minValue,
    maxValue,
    asRows,
    asColumns,
    sum = sum',
    difference,
    abs = abs',
    negative,
    filter = filter',
    all = all',
    any = any',
    product,
    entryWiseProduct,
    concatHorizontal,
    concatVertical,
    rowSlice,
    columnSlice,
    newMatrix,
    newRowVector,
    newColumnVector,
    newSparseMatrix,
    enumerate,
    format,
    print = print',
}
as
{
    size is matrix_t -> { rows is number, columns is number },
    width is matrix_t -> number,
    height is matrix_t -> number,
    density is matrix_t -> number,
    nonZeroValues is matrix_t -> number,
    at is matrix_t -> number -> number -> number,
    getColumn is number -> matrix_t -> vec.vector_t,
    getRow is number -> matrix_t -> vec.vector_t,
    getDiagonal is number -> matrix_t -> vec.vector_t,
    isRowMajor? is matrix_t -> boolean,
    isSparse? is matrix_t -> boolean,
    generate is (number -> number -> number) -> { rows is number, columns is number } -> matrix_t,
    constMatrix is number -> { rows is number, columns is number } -> matrix_t,
    randomMatrix is { rows is number, columns is number } -> matrix_t,
    zeroMatrix is { rows is number, columns is number } -> matrix_t, 
    identityMatrix is { rows is number, columns is number } -> matrix_t, 
    zeroSizeMatrix is () -> matrix_t,
    empty? is matrix_t -> boolean,
    equal is matrix_t -> matrix_t -> boolean,
    equalUnder is (number -> number -> boolean) -> matrix_t -> matrix_t -> boolean,
    transposed is matrix_t -> matrix_t,
    flipped is matrix_t -> matrix_t, 
    toRowMajor is matrix_t -> matrix_t, 
    toColumnMajor is matrix_t -> matrix_t,
    toSparse is matrix_t -> matrix_t,
    toDense is matrix_t -> matrix_t,
    scaled is number -> matrix_t -> matrix_t,
    resizedTo is { rows is number, columns is number } -> matrix_t -> matrix_t,
    minValue is matrix_t -> number,
    maxValue is matrix_t -> number,
    asRows is matrix_t -> list<vec.vector_t>, 
    asColumns is matrix_t -> list<vec.vector_t>,
    sum is matrix_t -> matrix_t -> matrix_t,
    difference is matrix_t -> matrix_t -> matrix_t,
    abs is matrix_t -> matrix_t,
    negative is matrix_t -> matrix_t,
    filter is (number -> boolean) -> matrix_t -> matrix_t,
    all is (number -> boolean) -> matrix_t -> boolean,
    any is (number -> boolean) -> matrix_t -> boolean,
    product is matrix_t -> matrix_t -> matrix_t,
    entryWiseProduct is matrix_t -> matrix_t -> matrix_t,
    concatHorizontal is list<matrix_t> -> matrix_t,
    concatVertical is list<matrix_t> -> matrix_t,
    rowSlice is matrix_t -> number -> number -> matrix_t, 
    columnSlice is matrix_t -> number -> number -> matrix_t,
    newMatrix is (ColumnMajor () | RowMajor ()) -> list<vec.vector_t> -> matrix_t, 
    newRowVector is vec.vector_t -> matrix_t, 
    newColumnVector is vec.vector_t -> matrix_t,
    newSparseMatrix is (ColumnMajor () | RowMajor ()) -> { rows is number, columns is number } -> list<{ i is number, j is number, v is number }> -> matrix_t,
    enumerate is matrix_t -> list<{ i is number, j is number, v is number }>,
    format is matrix_t -> string,
    print is matrix_t -> (),
}