• R/O
  • HTTP
  • SSH
  • HTTPS

Commit

Tags
No Tags

Frequently used words (click to add to your profile)

javac++androidlinuxc#windowsobjective-ccocoa誰得qtpythonphprubygameguibathyscaphec計画中(planning stage)翻訳omegatframeworktwitterdomtestvb.netdirectxゲームエンジンbtronarduinopreviewer

Mercury Geometry and Math Library


Commit MetaInfo

Revisão41d171250634ca20db35cab679afc6c030af30ae (tree)
Hora2022-04-18 04:04:53
AutorAlaskanEmily <emily@alas...>
CommiterAlaskanEmily

Mensagem de Log

Move the entire library into its own module

Mudança Sumário

  • delete: geometry.m => mmath.geometry.m
  • delete: geometry.plane.m => mmath.geometry.plane.m
  • delete: geometry.segment.m => mmath.geometry.segment.m
  • delete: geometry.triangle.m => mmath.geometry.triangle.m
  • delete: geometry2d.m => mmath.geometry2d.m
  • delete: geometry2d.rtree.m => mmath.geometry2d.rtree.m
  • delete: matrix.invert.m => mmath.matrix.invert.m
  • delete: matrix.m => mmath.matrix.m
  • modified: mmath.m (diff)
  • delete: multi_math.m => mmath.multi_math.m
  • delete: polyhedron.m => mmath.polyhedron.m
  • delete: unproject.m => mmath.unproject.m
  • delete: vector.m => mmath.vector.m
  • delete: vector.vector2.m => mmath.vector.vector2.m
  • delete: vector.vector3.m => mmath.vector.vector3.m
  • delete: vector.vector4.m => mmath.vector.vector4.m

Diff

--- a/geometry.m
+++ b/mmath.geometry.m
@@ -4,25 +4,25 @@
44 % License, v. 2.0. If a copy of the MPL was not distributed with this
55 % file, You can obtain one at http://mozilla.org/MPL/2.0/.
66
7-:- module geometry.
7+:- module mmath.geometry.
88
99 %==============================================================================%
1010 :- interface.
1111 %==============================================================================%
1212
13-:- import_module vector.
13+:- import_module mmath.vector.
1414
1515 %------------------------------------------------------------------------------%
1616
17-:- include_module geometry.triangle.
18-:- include_module geometry.segment.
19-:- include_module geometry.plane.
17+:- include_module mmath.geometry.triangle.
18+:- include_module mmath.geometry.segment.
19+:- include_module mmath.geometry.plane.
2020
2121 %------------------------------------------------------------------------------%
2222
23-:- import_module geometry.triangle.
24-:- import_module geometry.segment.
25-:- import_module geometry.plane.
23+:- import_module mmath.geometry.triangle.
24+:- import_module mmath.geometry.segment.
25+:- import_module mmath.geometry.plane.
2626
2727 %------------------------------------------------------------------------------%
2828
@@ -59,7 +59,7 @@
5959
6060 :- import_module float.
6161
62-:- import_module vector.vector3.
62+:- import_module mmath.vector.vector3.
6363
6464 %------------------------------------------------------------------------------%
6565
--- a/geometry.plane.m
+++ b/mmath.geometry.plane.m
@@ -4,14 +4,14 @@
44 % License, v. 2.0. If a copy of the MPL was not distributed with this
55 % file, You can obtain one at http://mozilla.org/MPL/2.0/.
66
7-:- module geometry.plane.
7+:- module mmath.geometry.plane.
88
99 %==============================================================================%
1010 % Geometric operations related to a 3D plane.
1111 :- interface.
1212 %==============================================================================%
1313
14-:- import_module vector.
14+:- import_module mmath.vector.
1515
1616 %------------------------------------------------------------------------------%
1717
@@ -55,8 +55,8 @@
5555
5656 :- use_module math.
5757
58-:- import_module vector.vector3.
59-:- import_module vector.vector4.
58+:- import_module mmath.vector.vector3.
59+:- import_module mmath.vector.vector4.
6060
6161 %------------------------------------------------------------------------------%
6262
--- a/geometry.segment.m
+++ b/mmath.geometry.segment.m
@@ -1,10 +1,10 @@
1-% Copyright (C) 2017-2020 AlaskanEmily
1+% Copyright (C) 2017-2022 AlaskanEmily
22 %
33 % This Source Code Form is subject to the terms of the Mozilla Public
44 % License, v. 2.0. If a copy of the MPL was not distributed with this
55 % file, You can obtain one at http://mozilla.org/MPL/2.0/.
66
7-:- module geometry.segment.
7+:- module mmath.geometry.segment.
88
99 %==============================================================================%
1010 % Geometric operations related to a segment. This is parametric on the vector
@@ -12,9 +12,10 @@
1212 :- interface.
1313 %==============================================================================%
1414
15-:- import_module vector.
1615 :- import_module pair.
1716
17+:- import_module mmath.vector.
18+
1819 %------------------------------------------------------------------------------%
1920
2021 :- type segment(V) ---> segment(p1::V, p2::V).
@@ -82,7 +83,8 @@
8283 %==============================================================================%
8384
8485 :- import_module float.
85-:- import_module vector.vector2.
86+
87+:- import_module mmath.vector.vector2.
8688
8789 %------------------------------------------------------------------------------%
8890
--- a/geometry.triangle.m
+++ b/mmath.geometry.triangle.m
@@ -1,10 +1,10 @@
1-% Copyright (C) 2017-2020 AlaskanEmily
1+% Copyright (C) 2017-2022 AlaskanEmily
22 %
33 % This Source Code Form is subject to the terms of the Mozilla Public
44 % License, v. 2.0. If a copy of the MPL was not distributed with this
55 % file, You can obtain one at http://mozilla.org/MPL/2.0/.
66
7-:- module geometry.triangle.
7+:- module mmath.geometry.triangle.
88
99 %==============================================================================%
1010 % Geometric operations related to a triangle. This is parametric on the vector
@@ -12,7 +12,7 @@
1212 :- interface.
1313 %==============================================================================%
1414
15-:- import_module vector.
15+:- import_module mmath.vector.
1616
1717 %------------------------------------------------------------------------------%
1818
@@ -33,8 +33,8 @@
3333
3434 %------------------------------------------------------------------------------%
3535
36-:- pragma type_spec(collinear/5, V = vector.vector2).
37-:- pragma type_spec(collinear/5, V = vector.vector3).
36+:- pragma type_spec(collinear/5, V = mmath.vector.vector2).
37+:- pragma type_spec(collinear/5, V = mmath.vector.vector3).
3838
3939 %==============================================================================%
4040 :- implementation.
--- a/geometry2d.m
+++ b/mmath.geometry2d.m
@@ -1,21 +1,22 @@
1-% Copyright (C) 2017-2020 AlaskanEmily
1+% Copyright (C) 2017-2022 AlaskanEmily
22 %
33 % This Source Code Form is subject to the terms of the Mozilla Public
44 % License, v. 2.0. If a copy of the MPL was not distributed with this
55 % file, You can obtain one at http://mozilla.org/MPL/2.0/.
66
7-:- module geometry2d.
7+:- module mmath.geometry2d.
88
99 %==============================================================================%
1010 :- interface.
1111 %==============================================================================%
1212
1313 :- import_module list.
14-:- import_module vector.
14+
15+:- import_module mmath.vector.
1516
1617 %------------------------------------------------------------------------------%
1718
18-:- include_module geometry2d.rtree.
19+:- include_module mmath.geometry2d.rtree.
1920
2021 %------------------------------------------------------------------------------%
2122
@@ -224,10 +225,10 @@
224225 :- use_module math.
225226 :- import_module float.
226227
227-:- use_module geometry.
228-:- use_module geometry.segment.
229-:- use_module multi_math.
230-:- import_module vector.vector2.
228+:- use_module mmath.geometry.
229+:- use_module mmath.geometry.segment.
230+:- use_module mmath.multi_math.
231+:- import_module mmath.vector.vector2.
231232
232233 %------------------------------------------------------------------------------%
233234
@@ -284,8 +285,8 @@ rectangle_intersection(rectangle(X1, Y1, W1, H1),
284285 rectangle(X2, Y2, W2, H2),
285286 rectangle(Left + 0.0, Top + 0.0, OutW, OutH)) :-
286287
287- multi_math.sub(Right, Left, OutW),
288- multi_math.sub(Bottom, Top, OutH),
288+ mmath.multi_math.sub(Right, Left, OutW),
289+ mmath.multi_math.sub(Bottom, Top, OutH),
289290
290291 % Logically required for an intersection to have occurred
291292 Bottom >= Top,
@@ -307,8 +308,8 @@ rectangle_union(rectangle(X1, Y1, W1, H1),
307308 rectangle(X2, Y2, W2, H2),
308309 rectangle(Left + 0.0, Top + 0.0, OutW, OutH)) :-
309310
310- multi_math.sub(Right, Left, OutW),
311- multi_math.sub(Bottom, Top, OutH),
311+ mmath.multi_math.sub(Right, Left, OutW),
312+ mmath.multi_math.sub(Bottom, Top, OutH),
312313
313314 Left = min(X1, X2),
314315 Top = min(Y1, Y2),
@@ -388,8 +389,8 @@ collide_segments(S1, S2, Point) :-
388389 S1 = segment(S1X1, S1Y1, S1X2, S1Y2),
389390 S2 = segment(S2X1, S2Y1, S2X2, S2Y2),
390391
391- Box1 = grow_rectangle(float.epsilon, geometry2d.bounding_box(S1)),
392- Box2 = grow_rectangle(float.epsilon, geometry2d.bounding_box(S2)),
392+ Box1 = grow_rectangle(float.epsilon, mmath.geometry2d.bounding_box(S1)),
393+ Box2 = grow_rectangle(float.epsilon, mmath.geometry2d.bounding_box(S2)),
393394 rectangle_intersection(Box1, Box2, IntersectedBox),
394395 grow_rectangle(float.epsilon, IntersectedBox, GrownIntersectedBox),
395396 point_inside(GrownIntersectedBox, Point),
@@ -585,7 +586,7 @@ triangle_intersects_segments(Triangle, Segments, OutPoint) :-
585586
586587 %------------------------------------------------------------------------------%
587588
588-point_to_vector(geometry2d.point(X, Y)) = vector.vector2.vector(X, Y).
589+point_to_vector(geometry2d.point(X, Y)) = vector(X, Y).
589590
590591 %------------------------------------------------------------------------------%
591592
@@ -659,8 +660,8 @@ point_to_vector(geometry2d.point(X, Y)) = vector.vector2.vector(X, Y).
659660 (bounding_box(point(X, Y)) = rectangle(X, Y, 0.0, 0.0)),
660661 (point_inside(P, P)),
661662 (translate(point(XT, YT), point(XIn, YIn), point(XOut, YOut)) :-
662- multi_math.add(XT, XIn, XOut),
663- multi_math.add(YT, YIn, YOut)),
663+ mmath.multi_math.add(XT, XIn, XOut),
664+ mmath.multi_math.add(YT, YIn, YOut)),
664665 (convex(Point, 0.0, [Point|[]])),
665666 scale(ScaleX, ScaleY, point(X, Y)) = point(ScaleX*X, ScaleY*Y)
666667 ].
@@ -678,26 +679,26 @@ point_to_vector(geometry2d.point(X, Y)) = vector.vector2.vector(X, Y).
678679 H = max(max(Y1, Y2), Y3) - Y),
679680 (point_inside(triangle(X1, Y1, X2, Y2, X3, Y3), point(PX, PY)) :-
680681 % Find the side of the point for each segment
681- Pos = vector.vector2.vector(PX, PY),
682- Vector1 = vector.vector2.vector(X1, Y1),
683- Vector2 = vector.vector2.vector(X2, Y2),
684- Vector3 = vector.vector2.vector(X3, Y3),
685- Segment1 = geometry.segment.segment(Vector1, Vector2),
686- Segment2 = geometry.segment.segment(Vector2, Vector3),
687- Segment3 = geometry.segment.segment(Vector3, Vector1),
682+ Pos = vector(PX, PY),
683+ Vector1 = vector(X1, Y1),
684+ Vector2 = vector(X2, Y2),
685+ Vector3 = vector(X3, Y3),
686+ Segment1 = mmath.geometry.segment.segment(Vector1, Vector2),
687+ Segment2 = mmath.geometry.segment.segment(Vector2, Vector3),
688+ Segment3 = mmath.geometry.segment.segment(Vector3, Vector1),
688689
689- Side1 = geometry.segment.side(Segment1, Pos),
690- Side2 = geometry.segment.side(Segment2, Pos),
691- Side3 = geometry.segment.side(Segment3, Pos),
690+ Side1 = mmath.geometry.segment.side(Segment1, Pos),
691+ Side2 = mmath.geometry.segment.side(Segment2, Pos),
692+ Side3 = mmath.geometry.segment.side(Segment3, Pos),
692693
693694 % Either the point must be colinear, or we must be on the same side of
694695 % all three segments.
695696 (
696- Side1 = geometry.segment.colinear
697+ Side1 = mmath.geometry.segment.colinear
697698 ;
698- Side2 = geometry.segment.colinear
699+ Side2 = mmath.geometry.segment.colinear
699700 ;
700- Side3 = geometry.segment.colinear
701+ Side3 = mmath.geometry.segment.colinear
701702 ;
702703 Side1 = Side2,
703704 Side2 = Side3
--- a/geometry2d.rtree.m
+++ b/mmath.geometry2d.rtree.m
@@ -1,10 +1,10 @@
1-% Copyright (C) 2018-2020 AlaskanEmily
1+% Copyright (C) 2018-2022 AlaskanEmily
22 %
33 % This Source Code Form is subject to the terms of the Mozilla Public
44 % License, v. 2.0. If a copy of the MPL was not distributed with this
55 % file, You can obtain one at http://mozilla.org/MPL/2.0/.
66
7-:- module geometry2d.rtree.
7+:- module mmath.geometry2d.rtree.
88
99 %==============================================================================%
1010 % Implements rtree typeclass for the geometry2d.rectangle type
@@ -16,20 +16,20 @@
1616
1717 %------------------------------------------------------------------------------%
1818
19-:- instance rtree.region(geometry2d.rectangle).
19+:- instance rtree.region(rectangle).
2020
2121 %------------------------------------------------------------------------------%
2222
23-:- type geometry2d.rtree.rtree(T) == rtree.rtree(geometry2d.rectangle, T).
23+:- type geometry2d.rtree.rtree(T) == rtree.rtree(rectangle, T).
2424
2525 %------------------------------------------------------------------------------%
2626
27-:- pred find(rtree.rtree(geometry2d.rectangle, T), geometry2d.point, T).
27+:- pred find(rtree.rtree(rectangle, T), point, T).
2828 :- mode find(in, in, out) is semidet.
2929
3030 %------------------------------------------------------------------------------%
3131
32-:- pred find_all(rtree.rtree(geometry2d.rectangle, T), geometry2d.point, list(T)).
32+:- pred find_all(rtree.rtree(rectangle, T), point, list(T)).
3333 :- mode find_all(in, in, out) is semidet.
3434
3535 %==============================================================================%
@@ -44,15 +44,15 @@ find(Tree, Point, Out) :- find_all(Tree, Point, [Out|_]).
4444
4545 %------------------------------------------------------------------------------%
4646
47-find_all(Tree, geometry2d.point(X, Y),
48- rtree.search_contains(Tree, geometry2d.rectangle(X, Y, 1.0, 1.0))).
47+find_all(Tree, point(X, Y),
48+ rtree.search_contains(Tree, rectangle(X, Y, 1.0, 1.0))).
4949
5050 %------------------------------------------------------------------------------%
5151
5252 :- instance rtree.region(rectangle) where [
53- (intersects(R1, R2) :- geometry2d.rectangles_intersect(R1, R2)),
54- rtree.bounding_region(R1, R2) = geometry2d.rectangle_union(R1, R2),
55- (contains(R1, R2) :- geometry2d.rectangle_contains(R1, R2)),
53+ (intersects(R1, R2) :- rectangles_intersect(R1, R2)),
54+ rtree.bounding_region(R1, R2) = rectangle_union(R1, R2),
55+ (contains(R1, R2) :- rectangle_contains(R1, R2)),
5656 rtree.size(rectangle(_, _, W, H)) = (W * H),
5757 (rtree.bounding_region_size(
5858 rectangle(X1, Y1, W1, H1),
--- a/mmath.m
+++ b/mmath.m
@@ -12,17 +12,9 @@
1212 :- interface.
1313 %==============================================================================%
1414
15-% This exists to satisfy the 2019-10-16 rotd, which had a bug/unintended-feature
16-% that prevented a module that only did imports from working.
17-:- pred dummy(T::in) is semidet.
15+:- include_module mmath.vector.
16+:- include_module mmath.geometry.
17+:- include_module mmath.matrix.
18+:- include_module mmath.geometry2d.
19+:- include_module mmath.multi_math.
1820
19-:- implementation.
20-
21-:- import_module vector.
22-:- import_module geometry.
23-:- import_module matrix.
24-:- import_module geometry2d.
25-:- import_module multi_math.
26-
27-:- pragma no_inline(dummy/1).
28-dummy(_).
--- a/matrix.invert.m
+++ b/mmath.matrix.invert.m
@@ -1,10 +1,10 @@
1-% Copyright (C) 2017-2020 AlaskanEmily
1+% Copyright (C) 2017-2022 AlaskanEmily
22 %
33 % This Source Code Form is subject to the terms of the Mozilla Public
44 % License, v. 2.0. If a copy of the MPL was not distributed with this
55 % file, You can obtain one at http://mozilla.org/MPL/2.0/.
66
7-:- module matrix.invert.
7+:- module mmath.matrix.invert.
88
99 %==============================================================================%
1010 % Inversion operations on matrices.
@@ -21,8 +21,8 @@
2121 :- implementation.
2222 %==============================================================================%
2323
24-:- import_module vector.
25-:- import_module vector.vector4.
24+:- import_module mmath.vector.
25+:- import_module mmath.vector.vector4.
2626
2727 % Input
2828 % 0-A 1-B 2-C 3-D
@@ -39,7 +39,7 @@
3939 invert(In) = matrix(OutA * Det, OutB * Det, OutC * Det, OutD * Det) :-
4040
4141 % Compute the determinant.
42- Det = (1.0 / vector.dot(column_a(In), OutA)),
42+ Det = (1.0 / dot(column_a(In), OutA)),
4343
4444 % Calculate the cofactors for the first two rows
4545 A = (In ^ c ^ z) * (In ^ d ^ w), % 0
@@ -56,7 +56,7 @@ invert(In) = matrix(OutA * Det, OutB * Det, OutC * Det, OutD * Det) :-
5656 L = (In ^ b ^ z) * (In ^ a ^ w), % 11
5757
5858 % Calculate the first two rows using the cofactors.
59- OutA = vector.vector4.vector(
59+ OutA = mmath.vector.vector4.vector(
6060 (A * In ^ b ^ y) + (D * In ^ c ^ y) + (E * In ^ d ^ y)
6161 -((B * In ^ b ^ y) + (C * In ^ c ^ y) + (F * In ^ d ^ y)),
6262 (B * In ^ a ^ y) + (G * In ^ c ^ y) + (J * In ^ d ^ y)
@@ -66,7 +66,7 @@ invert(In) = matrix(OutA * Det, OutB * Det, OutC * Det, OutD * Det) :-
6666 (F * In ^ a ^ y) + (I * In ^ b ^ y) + (L * In ^ c ^ y)
6767 -((E * In ^ a ^ y) + (J * In ^ b ^ y) + (K * In ^ c ^ y))),
6868
69- OutB = vector.vector4.vector(
69+ OutB = mmath.vector.vector4.vector(
7070 (B * In ^ b ^ x) + (C * In ^ c ^ x) + (F * In ^ d ^ x)
7171 -((A * In ^ b ^ x) + (D * In ^ c ^ x) + (E * In ^ d ^ x)),
7272 (A * In ^ a ^ x) + (H * In ^ c ^ x) + (I * In ^ d ^ x)
@@ -90,7 +90,7 @@ invert(In) = matrix(OutA * Det, OutB * Det, OutC * Det, OutD * Det) :-
9090 W = (In ^ a ^ x) * (In ^ b ^ y), % 10
9191 X = (In ^ b ^ x) * (In ^ a ^ y), % 11
9292
93- OutC = vector.vector4.vector(
93+ OutC = mmath.vector.vector4.vector(
9494 (M * In ^ b ^ w) + (P * In ^ c ^ w) + (Q * In ^ d ^ w)
9595 -((N * In ^ b ^ w) + (O * In ^ c ^ w) + (R * In ^ d ^ w)),
9696 (N * In ^ a ^ w) + (S * In ^ c ^ w) + (V * In ^ d ^ w)
@@ -100,7 +100,7 @@ invert(In) = matrix(OutA * Det, OutB * Det, OutC * Det, OutD * Det) :-
100100 (R * In ^ a ^ w) + (U * In ^ b ^ w) + (X * In ^ c ^ w)
101101 -((Q * In ^ a ^ w) + (V * In ^ b ^ w) + (W * In ^ c ^ w))),
102102
103- OutD = vector.vector4.vector(
103+ OutD = mmath.vector.vector4.vector(
104104 (N * In ^ b ^ z) + (O * In ^ c ^ z) + (R * In ^ d ^ z)
105105 -((M * In ^ b ^ z) + (P * In ^ c ^ z) + (Q * In ^ d ^ z)),
106106 (M * In ^ a ^ z) + (T * In ^ c ^ z) + (U * In ^ d ^ z)
--- a/matrix.m
+++ b/mmath.matrix.m
@@ -1,27 +1,27 @@
1-% Copyright (C) 2017-2020 AlaskanEmily
1+% Copyright (C) 2017-2022 AlaskanEmily
22 %
33 % This Source Code Form is subject to the terms of the Mozilla Public
44 % License, v. 2.0. If a copy of the MPL was not distributed with this
55 % file, You can obtain one at http://mozilla.org/MPL/2.0/.
66
7-:- module matrix.
7+:- module mmath.matrix.
88
99 %=============================================================================%
1010 :- interface.
1111 %=============================================================================%
1212
13-:- use_module vector.
13+:- use_module mmath.vector.
1414
15-:- include_module matrix.invert.
16-:- use_module matrix.invert.
15+:- include_module mmath.matrix.invert.
16+:- use_module mmath.matrix.invert.
1717
1818 %-----------------------------------------------------------------------------%
1919
2020 :- type matrix ---> matrix(
21- a::vector.vector4,
22- b::vector.vector4,
23- c::vector.vector4,
24- d::vector.vector4).
21+ a::mmath.vector.vector4,
22+ b::mmath.vector.vector4,
23+ c::mmath.vector.vector4,
24+ d::mmath.vector.vector4).
2525
2626 %-----------------------------------------------------------------------------%
2727 % frustum(Left, Right, Top, Bottom, Near, Far) = Frustum.
@@ -34,23 +34,39 @@
3434 %-----------------------------------------------------------------------------%
3535
3636 :- func translate(float, float, float) = matrix.
37+:- mode translate(in, in, in) = (out) is det.
38+:- mode translate(di, di, di) = (uo) is det.
39+:- mode translate(mdi, mdi, mdi) = (muo) is det.
3740
3841 %-----------------------------------------------------------------------------%
3942
40-:- func translate(vector.vector3) = matrix.
43+:- func translate(mmath.vector.vector3) = matrix.
44+:- mode translate(in) = (out) is det.
45+:- mode translate(di) = (uo) is det.
46+:- mode translate(mdi) = (muo) is det.
4147
4248 %-----------------------------------------------------------------------------%
4349
4450 :- func scale(float, float, float) = matrix.
51+:- mode scale(in, in, in) = (out) is det.
52+:- mode scale(di, di, di) = (uo) is det.
53+:- mode scale(mdi, mdi, mdi) = (muo) is det.
4554
4655 %-----------------------------------------------------------------------------%
4756
48-:- func scale(vector.vector3) = matrix.
57+:- func scale(mmath.vector.vector3) = matrix.
58+:- mode scale(in) = (out) is det.
59+:- mode scale(di) = (uo) is det.
60+:- mode scale(mdi) = (muo) is det.
4961
5062 %-----------------------------------------------------------------------------%
5163
52-:- func rotate(float::in, vector.vector3::in) = (matrix::uo) is det.
53-:- func rotate_old(float::in, vector.vector3::in) = (matrix::uo) is det.
64+:- func rotate(float, mmath.vector.vector3) = matrix.
65+:- mode rotate(in, in) = (uo) is det.
66+:- mode rotate(di, di) = (uo) is det.
67+:- mode rotate(mdi, mdi) = (muo) is det.
68+
69+:- func rotate_old(float::in, mmath.vector.vector3::in) = (matrix::uo) is det.
5470
5571 %-----------------------------------------------------------------------------%
5672
@@ -59,6 +75,9 @@
5975 %-----------------------------------------------------------------------------%
6076
6177 :- func transpose(matrix) = matrix.
78+:- mode transpose(in) = (out) is det.
79+:- mode transpose(di) = (uo) is det.
80+:- mode transpose(mdi) = (muo) is det.
6281
6382 %-----------------------------------------------------------------------------%
6483
@@ -73,11 +92,11 @@
7392
7493 %-----------------------------------------------------------------------------%
7594
76-:- func (matrix::in) * (vector.vector4::in) = (vector.vector4::uo) is det.
95+:- func (matrix::in) * (mmath.vector.vector4::in) = (mmath.vector.vector4::uo) is det.
7796
7897 %-----------------------------------------------------------------------------%
7998
80-:- func transform(matrix::in, vector.vector4::in) = (vector.vector4::uo) is det.
99+:- func transform(matrix::in, mmath.vector.vector4::in) = (mmath.vector.vector4::uo) is det.
81100
82101 %-----------------------------------------------------------------------------%
83102
@@ -103,10 +122,10 @@
103122
104123 %-----------------------------------------------------------------------------%
105124
106-:- func column_a(matrix::in) = (vector.vector4::uo) is det.
107-:- func column_b(matrix::in) = (vector.vector4::uo) is det.
108-:- func column_c(matrix::in) = (vector.vector4::uo) is det.
109-:- func column_d(matrix::in) = (vector.vector4::uo) is det.
125+:- func column_a(matrix::in) = (mmath.vector.vector4::uo) is det.
126+:- func column_b(matrix::in) = (mmath.vector.vector4::uo) is det.
127+:- func column_c(matrix::in) = (mmath.vector.vector4::uo) is det.
128+:- func column_d(matrix::in) = (mmath.vector.vector4::uo) is det.
110129
111130 %-----------------------------------------------------------------------------%
112131
@@ -131,8 +150,8 @@
131150 :- import_module int.
132151 :- use_module math.
133152
134-:- import_module vector.vector3.
135-:- import_module vector.vector4.
153+:- import_module mmath.vector.vector3.
154+:- import_module mmath.vector.vector4.
136155
137156 %-----------------------------------------------------------------------------%
138157
@@ -192,7 +211,7 @@ rotate(A, Vec) = matrix(
192211 vector(Y*X*(1.0-C)+Z*S, Y*Y*(1.0-C)+C, Y*Z*(1.0-C)-X*S, 0.0),
193212 vector(Z*X*(1.0-C)-Y*S, Z*Y*(1.0-C)+X*S, Z*Z*(1.0-C)+C, 0.0),
194213 vector(0.0, 0.0, 0.0, 1.0)) :-
195- vector(X, Y, Z) = vector.normalize(Vec),
214+ vector(X, Y, Z) = mmath.vector.normalize(Vec),
196215 S = math.sin(A),
197216 C = math.cos(A).
198217
@@ -207,7 +226,7 @@ identity = matrix(
207226 %-----------------------------------------------------------------------------%
208227
209228 (matrix(V1, V2, V3, V4)) * (V) =
210- vector(vector.dot(V, V1), vector.dot(V, V2), vector.dot(V, V3), vector.dot(V, V4)).
229+ vector(mmath.vector.dot(V, V1), mmath.vector.dot(V, V2), mmath.vector.dot(V, V3), mmath.vector.dot(V, V4)).
211230
212231 %-----------------------------------------------------------------------------%
213232
@@ -234,10 +253,10 @@ transpose(
234253 %-----------------------------------------------------------------------------%
235254
236255 multiply(matrix(A, B, C, D), matrix(AIn, BIn, CIn, DIn)) = matrix(
237- vector(vector.dot(A, E), vector.dot(A, F), vector.dot(A, G), vector.dot(A, H)),
238- vector(vector.dot(B, E), vector.dot(B, F), vector.dot(B, G), vector.dot(B, H)),
239- vector(vector.dot(C, E), vector.dot(C, F), vector.dot(C, G), vector.dot(C, H)),
240- vector(vector.dot(D, E), vector.dot(D, F), vector.dot(D, G), vector.dot(D, H))) :-
256+ vector(mmath.vector.dot(A, E), mmath.vector.dot(A, F), mmath.vector.dot(A, G), mmath.vector.dot(A, H)),
257+ vector(mmath.vector.dot(B, E), mmath.vector.dot(B, F), mmath.vector.dot(B, G), mmath.vector.dot(B, H)),
258+ vector(mmath.vector.dot(C, E), mmath.vector.dot(C, F), mmath.vector.dot(C, G), mmath.vector.dot(C, H)),
259+ vector(mmath.vector.dot(D, E), mmath.vector.dot(D, F), mmath.vector.dot(D, G), mmath.vector.dot(D, H))) :-
241260 E = vector(AIn ^ x, BIn ^ x, CIn ^ x, DIn ^ x),
242261 F = vector(AIn ^ y, BIn ^ y, CIn ^ y, DIn ^ y),
243262 G = vector(AIn ^ z, BIn ^ z, CIn ^ z, DIn ^ z),
--- a/multi_math.m
+++ b/mmath.multi_math.m
@@ -1,10 +1,10 @@
1-% Copyright (C) 2018-2020 AlaskanEmily
1+% Copyright (C) 2018-2022 AlaskanEmily
22 %
33 % This Source Code Form is subject to the terms of the Mozilla Public
44 % License, v. 2.0. If a copy of the MPL was not distributed with this
55 % file, You can obtain one at http://mozilla.org/MPL/2.0/.
66
7-:- module multi_math.
7+:- module mmath.multi_math.
88
99 %==============================================================================%
1010 :- interface.
--- a/vector.m
+++ b/mmath.vector.m
@@ -1,28 +1,28 @@
1-% Copyright (C) 2017-2020 AlaskanEmily
1+% Copyright (C) 2017-2022 AlaskanEmily
22 %
33 % This Source Code Form is subject to the terms of the Mozilla Public
44 % License, v. 2.0. If a copy of the MPL was not distributed with this
55 % file, You can obtain one at http://mozilla.org/MPL/2.0/.
66
7-:- module vector.
7+:- module mmath.vector.
88
99 %==============================================================================%
1010 :- interface.
1111 %==============================================================================%
1212
13-:- include_module vector.vector2.
14-:- include_module vector.vector3.
15-:- include_module vector.vector4.
13+:- include_module mmath.vector.vector2.
14+:- include_module mmath.vector.vector3.
15+:- include_module mmath.vector.vector4.
1616
17-:- use_module vector.vector2.
18-:- use_module vector.vector3.
19-:- use_module vector.vector4.
17+:- use_module mmath.vector.vector2.
18+:- use_module mmath.vector.vector3.
19+:- use_module mmath.vector.vector4.
2020
2121 %------------------------------------------------------------------------------%
2222
23-:- type vector2 == vector.vector2.vector.
24-:- type vector3 == vector.vector3.vector.
25-:- type vector4 == vector.vector4.vector.
23+:- type vector2 == mmath.vector.vector2.vector.
24+:- type vector3 == mmath.vector.vector3.vector.
25+:- type vector4 == mmath.vector.vector4.vector.
2626
2727 %------------------------------------------------------------------------------%
2828
--- a/vector.vector2.m
+++ b/mmath.vector.vector2.m
@@ -4,20 +4,18 @@
44 % License, v. 2.0. If a copy of the MPL was not distributed with this
55 % file, You can obtain one at http://mozilla.org/MPL/2.0/.
66
7-:- module vector.vector2.
7+:- module mmath.vector.vector2.
88
99 %==============================================================================%
1010 % 2D vector implementation.
1111 :- interface.
1212 %==============================================================================%
1313
14-:- use_module vector.
15-
1614 :- type vector ---> vector(x::float, y::float).
1715
1816 %------------------------------------------------------------------------------%
1917
20-:- instance vector.vector(vector2).
18+:- instance vector(vector2).
2119
2220 %------------------------------------------------------------------------------%
2321
@@ -132,7 +130,7 @@ cross(vector(X1, Y1), vector(X2, Y2)) = (X1 * Y2) - (Y1 * X2).
132130
133131 %------------------------------------------------------------------------------%
134132
135-:- instance vector.vector(vector2) where [
133+:- instance vector(vector2) where [
136134 magnitude_squared(vector(X, Y)) = ((X*X) + (Y*Y)),
137135 scale(vector(X, Y), S) = vector(X*S, Y*S),
138136 multiply(vector(X1, Y1), vector(X2, Y2)) = vector(X1*X2, Y1*Y2),
--- a/vector.vector3.m
+++ b/mmath.vector.vector3.m
@@ -1,10 +1,10 @@
1-% Copyright (C) 2017-2020 AlaskanEmily
1+% Copyright (C) 2017-2022 AlaskanEmily
22 %
33 % This Source Code Form is subject to the terms of the Mozilla Public
44 % License, v. 2.0. If a copy of the MPL was not distributed with this
55 % file, You can obtain one at http://mozilla.org/MPL/2.0/.
66
7-:- module vector.vector3.
7+:- module mmath.vector.vector3.
88
99 %==============================================================================%
1010 % 3D vector implementation.
--- a/vector.vector4.m
+++ b/mmath.vector.vector4.m
@@ -1,10 +1,10 @@
1-% Copyright (C) 2017-2020 AlaskanEmily
1+% Copyright (C) 2017-2022 AlaskanEmily
22 %
33 % This Source Code Form is subject to the terms of the Mozilla Public
44 % License, v. 2.0. If a copy of the MPL was not distributed with this
55 % file, You can obtain one at http://mozilla.org/MPL/2.0/.
66
7-:- module vector.vector4.
7+:- module mmath.vector.vector4.
88
99 %==============================================================================%
1010 % 4D vector implementation.