Matrix.st
author Claus Gittinger <cg@exept.de>
Wed, 21 Aug 2019 11:47:34 +0200
changeset 5121 19ef82c3b471
parent 5109 d15cce8be8fa
child 5134 4bf59b461b6b
permissions -rw-r--r--
#FEATURE by exept class: Matrix added: #setDimensions:

"{ Encoding: utf8 }"

"{ Package: 'stx:libbasic2' }"

"{ NameSpace: Smalltalk }"

AbstractMultidimensionalArray variableSubclass:#Matrix
	instanceVariableNames:'dimensions'
	classVariableNames:''
	poolDictionaries:''
	category:'Collections-MultiDimensional'
!

!Matrix class methodsFor:'documentation'!

documentation
"
    Generic Matrix with arbitrary number of dimensions.
    Especially useful with the ArrayIndexing-Parser extension.

    [author:]
        Claus Gittinger (cg@sinir)

    [instance variables:]

    [class variables:]

    [see also:]
        MatrixAccessor
"
!

examples
"

  You have to enable the Parsers arrayIndexingExtension support
  in order to be able to execute the examples below.

  Parser allowArrayIndexSyntaxExtension:true

                                                                [exBegin]
    |m|

    m := Matrix[3,3].
    m[2,1] := 11.
    m[2,2] := 12.
    m[2,3] := 13.
    m     
                                                                [exEnd]

                                                                [exBegin]
    |m|

    m := Matrix3_3 new.
    m[2,1] := 11.
    m[2,2] := 12.
    m[2,3] := 13.
    m       
                                                                [exEnd]

                                                                [exBegin]
    |m1 m2|

    m1 := Matrix3_3 new.
    m1 atAllPut:1.

    m2 := Matrix3_3 new.
    m2 atAllPut:2.

    m1 - m2    
                                                                [exEnd]

                                                                [exBegin]
    |m1 m2|

    m1 := Matrix3_3 new.
    m1 atAllPut:1.

    m2 := Matrix3_3 new.
    m2 atAllPut:2.

    m1 + m2    
                                                                [exEnd]
"
! !

!Matrix class methodsFor:'instance creation'!

_at:nIndices
    "this is a synthetic selector, generated by the compiler,
     if a construct of the form expr[idx...] is parsed.
     I.e. 
        Matrix[n]
     generates
        Matrix _at: n
    "

    ^ Array new:nIndices
!

_at:dim1 at:dim2
    "this is a synthetic selector, generated by the compiler,
     if a construct of the form expr[idx...] is parsed.
     I.e. 
        Matrix[n,m]
     generates
        Matrix _at:n at:m
    "

    ^ self newForRows:dim1 cols:dim2
!

_at:dim1 at:dim2 at:dim3
    "this is a synthetic selector, generated by the compiler,
     if a construct of the form expr[idx...] is parsed.
     I.e. 
        Matrix[n,m,o]
     generates
        Matrix _at:n at:m at:o
    "

    ^ (self basicNew:(dim1 * dim2 * dim3))
        dimensions:(Array with:dim1 with:dim2 with:dim3)
!

identity: anInteger
    "Answer an identity matrix of order 'anInteger@anInteger'."

    | mat |

    mat := self newForRows:anInteger cols:anInteger.
    mat atAllPut:0.
    1 to: anInteger do: [ :i | mat _at: i at: i put: 1 ].
    ^ mat

    "
     self identity:3
     self identity:2
     self identity:5
    "
!

newForRows:nRows cols:nCols
    |mClass|

    nRows == nCols ifTrue:[
        nCols == 2 ifTrue:[
            ^ Matrix2_2 new dimensions:#(2 2)
        ].
        nCols == 3 ifTrue:[
            ^ Matrix3_3 new dimensions:#(3 3)
        ].
        mClass := SquareMatrix
    ] ifFalse:[
        mClass := self
    ].

    ^ (mClass basicNew:(nRows * nCols))
        dimensions:(Array with:nRows with:nCols)
!

ones: aPoint
    "Answer a matrix of order 'aPoint' filled with ones"

    |mat|

    mat := self newForRows:aPoint y cols:aPoint x.
    mat atAllPut: 1.
    ^ mat

    "
     self ones:(3 @ 3)
     self ones:(3 @ 2)
     self ones:(5 @ 5)
    "
!

zero: aPoint
    "Answer a matrix of order 'aPoint' filled with zeros"

    |mat|

    mat := self newForRows:aPoint y cols:aPoint x.
    mat atAllPut: 0.
    ^ mat

    "
     self zero:(3 @ 3)
     self zero:(3 @ 2)
     self zero:(5 @ 5)
    "
! !

!Matrix methodsFor:'accessing'!

_at:index
    "this is a synthetic selector, generated by the compiler,
     if a construct of the form expr[idx...] is parsed.
     I.e. 
        foo[n]
     generates
        foo _at: n
    "
    dimensions size ~~ 1 ifTrue:[self dimensionError].
    ^ self basicAt:index.
!

_at:index1 at:index2
    "this is a synthetic selector, generated by the compiler,
     if a construct of the form expr[idx...] is parsed.
     I.e. 
        foo[n,m]
     generates
        foo _at:n at:m
    "
    |idx|

    dimensions size ~~ 2 ifTrue:[self dimensionError].
    (index1 between:1 and:(dimensions at:1)) ifFalse:[self subscriptBoundsError:index1].
    (index2 between:1 and:(dimensions at:2)) ifFalse:[self subscriptBoundsError:index2].

    idx := ((index1-1) * (dimensions at:2)).
    idx := idx + index2.
    ^ self basicAt:idx.

    "
     |m|
     m := MatrixAccessor new
              collection:
                #(
                   11 12 13 14
                   21 22 23 24
                   31 32 33 34
                 )
              dimensions:
                #(3 4).

     m[1,4]          
    "
!

_at:index1 at:index2 at:index3
    "this is a synthetic selector, generated by the compiler,
     if a construct of the form expr[idx...] is parsed.
     I.e. 
        foo[n,m,o]
     generates
        foo _at:n at:m at:o
    "
    |idx|

    dimensions size ~~ 3 ifTrue:[self dimensionError].
    (index1 between:1 and:(dimensions at:1)) ifFalse:[self subscriptBoundsError:index1].
    (index2 between:1 and:(dimensions at:2)) ifFalse:[self subscriptBoundsError:index2].
    (index3 between:1 and:(dimensions at:3)) ifFalse:[self subscriptBoundsError:index3].

    idx := ((((index1-1) * (dimensions at:2)) + (index2-1)) * (dimensions at:3)).
    idx := idx + index3.
    ^ self basicAt:idx.

    "
     |m|
     m := MatrixAccessor new
              collection:
                #(
                   111 112 113 114
                   121 122 123 124
                   131 132 133 134

                   211 212 213 214
                   221 222 223 224
                   231 232 233 234 )
              dimensions:
                #(2 3 4).

     m[2,1,4]          
    "
!

_at:index1 at:index2 at:index3 put:val
    "this is a synthetic selector, generated by the compiler,
     if a construct of the form expr[idx...] := val is parsed.
     I.e. 
        foo[n,m,o] := val
     generates
        foo _at:n at:m at:o put:val
    "
    |idx|

    dimensions size ~~ 3 ifTrue:[self dimensionError].
    (index1 between:1 and:(dimensions at:1)) ifFalse:[self subscriptBoundsError:index1].
    (index2 between:1 and:(dimensions at:2)) ifFalse:[self subscriptBoundsError:index2].
    (index3 between:1 and:(dimensions at:3)) ifFalse:[self subscriptBoundsError:index3].

    idx := ((((index1-1) * (dimensions at:2)) + (index2-1)) * (dimensions at:3)).
    idx := idx + index3.
    ^ self basicAt:idx put:val.
!

_at:index1 at:index2 put:val
    "this is a synthetic selector, generated by the compiler,
     if a construct of the form expr[idx...] := val is parsed.
     I.e. 
        foo[n,m] := val
     generates
        foo _at:n at:m put:val
    "
    |idx|

    dimensions size ~~ 2 ifTrue:[self dimensionError].
    (index1 between:1 and:(dimensions at:1)) ifFalse:[self subscriptBoundsError:index1].
    (index2 between:1 and:(dimensions at:2)) ifFalse:[self subscriptBoundsError:index2].

    idx := ((index1-1) * (dimensions at:2)).
    idx := idx + index2.
    ^ self basicAt:idx put:val.
!

_at:index put:val
    "this is a synthetic selector, generated by the compiler,
     if a construct of the form expr[idx...] := val is parsed.
     I.e. 
        foo[n] := val
     generates
        foo _at:n put:val
    "
    dimensions size ~~ 1 ifTrue:[self dimensionError].
    ^ self basicAt:index put:val.
!

at:index
    "/ dimensions size ~~ 1 ifTrue:[self dimensionError].
    ^ self basicAt:index.
!

at:index put:val
    "/ dimensions size ~~ 1 ifTrue:[self dimensionError].
    ^ self basicAt:index put:val.
!

dimensions
    ^ dimensions
!

size
    ^ self basicSize
! !

!Matrix methodsFor:'arithmetic'!

+ aMatrix
    "Answer the result of adding 'aMatrix' to this matrix."

    ^ aMatrix sumFromMatrix:self
!

- aMatrix
    "Answer the result of subtracting 'aMatrix' from this matrix."

    ^ aMatrix differenceFromMatrix:self
!

= aMatrix
    "Answer true, if the argument represents the same matrix"

    self species == aMatrix species ifFalse: [ ^ false ].
    dimensions = aMatrix dimensions ifFalse: [ ^ false ].

    1 to: self basicSize do:[ :idx | 
        (aMatrix basicAt: idx) == (self basicAt: idx) ifFalse:[^ false].
    ].
    ^ true
!

differenceFromMatrix: aMatrix
    "Answer the result of subtracting the receiver from 'aMatrix'."

    | result |

    dimensions = aMatrix dimensions ifFalse: [ 
        IncompatibleMatrixError raiseRequestWith:aMatrix errorString:'argument matrix has different dimensions'
    ].

    result := (self class new:(self basicSize)) dimensions:dimensions.

    1 to: self basicSize do:[ :idx | 
        result basicAt: idx put: (aMatrix basicAt: idx) - (self basicAt: idx).
    ].
    ^ result
!

sumFromMatrix: aMatrix
    "Answer the result of adding 'aMatrix' to this matrix."

    | result |

    dimensions = aMatrix dimensions ifFalse: [
        IncompatibleMatrixError raiseRequestWith:aMatrix errorString:'argument matrix has different dimensions'
    ].

    result := (self class new:(self basicSize)) dimensions:dimensions.

    1 to: self basicSize do:[ :idx | 
        result basicAt: idx put: (self basicAt: idx) + (aMatrix basicAt: idx).
    ].
    ^ result
! !

!Matrix methodsFor:'matrix operations'!

determinant
    IncompatibleMatrixError raiseRequestWith:self errorString: 'Matrix must be square'
! !

!Matrix methodsFor:'private'!

dimensions:dimensionsArg
    dimensionsArg isArray ifFalse:[
        dimensions := Array with:dimensionsArg y with:dimensionsArg x.
    ] ifTrue:[
        dimensions := dimensionsArg.
    ].
!

setDimensions:dimensionsArg
    dimensions := dimensionsArg.

! !

!Matrix methodsFor:'queries'!

columns
    ^ dimensions at:2
!

isSquare
    ^ false

    "
     (self zero:(3 @ 3)) isSquare
     (self zero:(2 @ 2)) isSquare
     (self zero:(3 @ 2)) isSquare 
    "
!

rows
    ^ dimensions at:1
! !

!Matrix class methodsFor:'documentation'!

version_CVS
    ^ '$Header$'
! !