testing-framework / R / fit.r @ 17a68f48
History | View | Annotate | Download (7.465 KB)
1 | 8526ae8c | Jonas Diekmann | # Dies ist die Datei "fit.r". |
---|---|---|---|
2 | # Sie benutzt einen Levenberg-Marquardt-Algorithmus |
||
3 | # um Eulerwinkel zu bestimmen, die der gegebenen |
||
4 | # Rotationsmatrix möglicht gut entsprechen. |
||
5 | # Dadurch wird der Fehler aller Matritzeneinträge |
||
6 | # in den Eulerwinkeln abgebildet. |
||
7 | |||
8 | |||
9 | # Berechnet die Abweichung dreier angenäherter Winkel an eine Rotationsmatrix. |
||
10 | # Die Winkel werden in XYZ-Euler angenommen. |
||
11 | # a ist ein Zeilenvektor der Rotationsmatrix |
||
12 | # x ist ein Vektor der Rotationswinkel in XYZ-Euler |
||
13 | # Das Ergebnis ist ein Vektor, der die Differenz der aus den Winkeln berechneten Rotationsmatrix von der vorgegebenen Matrix angibt. |
||
14 | DiffXYZeulerRotmFIT <- function(x,a){ |
||
15 | ret <- numeric(10) |
||
16 | #cat("Diff",x,a,"\n") |
||
17 | #Die unten zugrundeliegende Berechnung der Rotationsmatrix entspricht der Darstellung in Weisstein (k.D.), wurde jedoch auf des verwendete Koordinatensystem (rechtshändig) und die Koordinatensysteme der verwendeten Bibliotheken umgerechnet |
||
18 | #cat(class(as.numeric(x[2]))) |
||
19 | ret[1]<- (cos(as.numeric(x[2]))*cos(as.numeric(x[3]))-as.numeric(a[3])) |
||
20 | ret[2]<- ((sin(as.numeric(x[1]))*sin(as.numeric(x[2]))*cos(as.numeric(x[3]))-sin(as.numeric(x[3]))*cos(as.numeric(x[1])))-as.numeric(a[4])) |
||
21 | ret[3]<- (cos(as.numeric(x[1]))*sin(as.numeric(x[2]))*cos(as.numeric(x[3]))+sin(as.numeric(x[1]))*sin(as.numeric(x[3]))-as.numeric(a[5])) |
||
22 | ret[4]<- (cos(as.numeric(x[2]))*sin(as.numeric(x[3]))-as.numeric(a[6])) |
||
23 | ret[5]<- (sin(as.numeric(x[1]))*sin(as.numeric(x[2]))*sin(as.numeric(x[3]))+cos(as.numeric(x[1]))*cos(as.numeric(x[3]))-as.numeric(a[7])) |
||
24 | ret[6]<- (cos(as.numeric(x[1]))*sin(as.numeric(x[2]))*sin(as.numeric(x[3]))-sin(as.numeric(x[1]))*cos(as.numeric(x[3]))-as.numeric(a[8])) |
||
25 | ret[7]<- (-sin(as.numeric(x[2])))-as.numeric(a[9]) |
||
26 | ret[8]<- (cos(as.numeric(x[2]))*sin(as.numeric(x[1]))-a[10]) |
||
27 | ret[9]<- (cos(as.numeric(x[1]))*cos(as.numeric(x[2]))-a[11]) |
||
28 | |||
29 | #Dieser Eintrag kann für Anpassungen der Gewichtsfunktion verwendet werden |
||
30 | ret[10]<- 0 |
||
31 | return(ret) |
||
32 | } |
||
33 | |||
34 | # Die obenstehende Methode läuft oft in lokale Minima und liefert dann falsche Werte. |
||
35 | # Um dies zu verhindern, werden die Werte für Blender aus 3 Gleichungen "analytisch" berechnet. (Das ist natürlich nicht wirklich eine analytische Rechnung, weil die trigonometrischen Funktionen nummerisch implementiert sein dürften). |
||
36 | startXYZeulerFIT <- function(a){ |
||
37 | |||
38 | toleranz = 1e-10 |
||
39 | |||
40 | ret <- c(-1,-1,-1) |
||
41 | |||
42 | #Bester Ansatz nach Slabaugh (2015) (Wesentliche Abweichungen sind angegeben) |
||
43 | if (abs(abs(a[7])-1) > toleranz) #Betrachte auch Werte sehr nahe an +-1 als +-1 |
||
44 | { |
||
45 | ret[2] <- asin(-a[7]) |
||
46 | #cat("Y-Euler:",ret[2]," ") |
||
47 | temp <- cos(ret[2]) |
||
48 | ret[1] <- atan2(a[8]/temp,a[9]/temp) |
||
49 | #cat("X-Euler:",ret[1]," ") |
||
50 | ret[3] <- atan2(a[4]/temp,a[1]/temp) |
||
51 | #cat("Z-Euler:",ret[3]," ",a[4]," ",a[1]," ",temp,"\n") |
||
52 | |||
53 | } |
||
54 | else |
||
55 | { |
||
56 | ret[3] <- (pi/2) # Die im Pseudocode von Slabaugh vorgeschlagene 0 ist für uns numerisch ungünstig |
||
57 | if(abs(a[7]+1) <= toleranz) #Betrachte auch Werte sehr nahe an -1 als -1 |
||
58 | { |
||
59 | ret[2] = pi/2 |
||
60 | ret[1] = (pi/2)+atan2(a[2],a[3]) |
||
61 | } |
||
62 | else |
||
63 | { |
||
64 | ret[2] = 3*pi/2 # Entspricht -pi/2 |
||
65 | ret[1] = atan2(-a[2],-a[3])-(pi/2) |
||
66 | } |
||
67 | } |
||
68 | |||
69 | #Sorgt für positive Winkel |
||
70 | for(i in 1:3){ |
||
71 | while(ret[i] < 0){ |
||
72 | ret[i] <- ret[i]+2*pi |
||
73 | } |
||
74 | } |
||
75 | return(ret) |
||
76 | } |
||
77 | |||
78 | #Wrapper für acos |
||
79 | #min, max behebt Probleme mit der Maschienengenauigkeit im Grenzbereich und verhindert Nans, weil Werte die Definitionsgrenze auf hinteren Nachkommastellen überschreiten (vgl. Bolker (2012)). |
||
80 | myacos <- function(x){ |
||
81 | return (acos(max(min(x,1.0),-1.0))) |
||
82 | } |
||
83 | |||
84 | # Diese Funktion führt alle notwendigen Schritte aus. |
||
85 | # Leider hat lsqnonlin ein Problem damit, wenn der perfekte Wert bereits im ersten Durchgang übergeben wird. Desshalb müssen wir vorher prüfen, ob wir bereits die optimale Lösung haben. |
||
86 | # a ist wieder die Rotationsmatrix |
||
87 | # x0 ist der Startwert |
||
88 | # init_rotm_inv ist die Inverse der für die Bibliothek benötigten Anpassungsmatrix. |
||
89 | Rot2XYZeulerFIT <- function(a,x0,init_rotm_inv) { |
||
90 | |||
91 | rotm <- as.numeric(as.character(a)) |
||
92 | ret <- numeric(5) |
||
93 | # Setze Frame und Markerid |
||
94 | ret[1] <- a[1] |
||
95 | ret[2] <- a[2] |
||
96 | |||
97 | # Korrigiere Eingabematrix |
||
98 | matA <- matrix(rotm[3:11],ncol=3,byrow=TRUE) |
||
99 | matA <- matA %*% init_rotm_inv |
||
100 | for(i in 0:2){ |
||
101 | rotm[(i*3+3):(i*3+5)] <- unlist(matA[(i+1),]) |
||
102 | } |
||
103 | #Berechne aktuellen Fehler |
||
104 | akterr <- pracma::rmserr(as.double(DiffXYZeulerRotmFIT(x=x0,a=rotm)),rep(0,10)) |
||
105 | #Sind wir nicht perfekt (mse = gemittelter quadratischer Fehler)? |
||
106 | if(akterr$mse > 0){ |
||
107 | #winkel2 <- pracma::gaussNewton(as.double(winkel),DiffXYZeulerRotmFIT,JacobiFIT,maxiter=250,a=as.double(rotm)) |
||
108 | winkel2 <- pracma::lsqnonlin(DiffXYZeulerRotmFIT,as.double(x0),options = list(tau=1e-9,maxeval=250),a=rotm) |
||
109 | newerr <- pracma::rmserr(as.double(DiffXYZeulerRotmFIT(x=winkel2$x,rotm)),rep(0,10)) |
||
110 | } |
||
111 | if(newerr$mse <= akterr$mse){ |
||
112 | #print("Verbesserung erfolgreich!") |
||
113 | #print(x0) |
||
114 | #print(winkel2$x) |
||
115 | ret[3:5] <- winkel2$x |
||
116 | return(ret) |
||
117 | } |
||
118 | else{ |
||
119 | #Verbesserung war nicht möglich |
||
120 | print("Warnung: Verbesserung gescheitert!") |
||
121 | print(akterr$mse) |
||
122 | print(newerr$mse) |
||
123 | print(x0) |
||
124 | print(winkel2$x) |
||
125 | ret[3:5] <- x0 |
||
126 | return(ret) |
||
127 | } |
||
128 | } |
||
129 | |||
130 | Rot2XYZeulerBART <- function(a,x0) { |
||
131 | #print("BART") |
||
132 | x0 <- unlist(x0) |
||
133 | #Drehrichtung um die X-Achse umdrehen |
||
134 | x0[1]<- (2*pi)-x0[1] |
||
135 | init_mat_table <- read.table(file="Bestimmung_Umformungen_Rotm/bart_init_rotm_inv.table") |
||
136 | init_rotm_inv <- matrix(unlist(init_mat_table), ncol=3, nrow=3, byrow=TRUE) |
||
137 | ret <- Rot2XYZeulerFIT(a,x0,init_rotm_inv) |
||
138 | #Drehrichtung um die X-Achse umdrehen |
||
139 | ret[[3]]<- (2*pi)-ret[[3]] |
||
140 | return(ret) |
||
141 | } |
||
142 | |||
143 | Rot2XYZeulerALVAR <- function(a,x0) { |
||
144 | #print("ALVAR") |
||
145 | x0 <- unlist(x0) |
||
146 | #Drehrichtung um die X-Achse umdrehen |
||
147 | x0[1]<- (2*pi)-x0[1] |
||
148 | init_mat_table <- read.table(file="Bestimmung_Umformungen_Rotm/alvar_init_rotm_inv.table") |
||
149 | init_rotm_inv <- matrix(unlist(init_mat_table), ncol=3, nrow=3, byrow=TRUE) |
||
150 | ret <- Rot2XYZeulerFIT(a,x0,init_rotm_inv) |
||
151 | #Drehrichtung um die X-Achse umdrehen |
||
152 | ret[[3]]<- (2*pi)-ret[[3]] |
||
153 | return(ret) |
||
154 | } |
||
155 | |||
156 | Rot2XYZeulerARUCO <- function(a,x0) { |
||
157 | #print("ARUCO") |
||
158 | #print(x0) |
||
159 | #Tausche die ersten beiden Zeilen |
||
160 | a[3:8] <- a[c(6:8,3:5)] |
||
161 | |||
162 | x0 <- unlist(x0) |
||
163 | #Drehrichtung um die Z-Achse umdrehen |
||
164 | x0[3] <- 2*pi-x0[3] |
||
165 | init_mat_table <- read.table(file="Bestimmung_Umformungen_Rotm/aruco_init_rotm_inv.table") |
||
166 | init_rotm_inv <- matrix(unlist(init_mat_table), ncol=3, nrow=3, byrow=TRUE) |
||
167 | ret <- Rot2XYZeulerFIT(a,x0,init_rotm_inv) |
||
168 | #Drehrichtung um die Z-Achse umdrehen |
||
169 | ret[[5]]<- (2*pi)-ret[[5]] |
||
170 | return(ret) |
||
171 | } |
||
172 | |||
173 | Rot2XYZeulerBLENDER <- function(a) { |
||
174 | rotm <- as.numeric(as.character(a)) |
||
175 | ret <- numeric(5) |
||
176 | # Setze Frame und Markerid |
||
177 | ret[1] <- a[1] |
||
178 | ret[2] <- a[2] |
||
179 | #Skalierung auf der Z-Achse ausgleichen |
||
180 | a[9:11] <- a[9:11]*200 |
||
181 | |||
182 | ret[3:5] <- startXYZeulerFIT(unlist(a[3:11])) |
||
183 | #Drehrichtung um die Y-Achse umdrehen |
||
184 | ret[4] <- 2*pi-unlist(ret[4]) |
||
185 | return(ret) |
||
186 | } |
||
187 | |||
188 | #Quellen: |
||
189 | #Bolker, B. (2012, 24. Dezember) acos(1) returns NaN for some values, not others Antwort auf http://stackoverflow.com/questions/18806944/about-arccos-function-in-r-nan-produced |
||
190 | #Slabaugh, G. G. (2015) Computing Euler angles from a rotation matrix http://staff.city.ac.uk/~sbbh653/publications/euler.pdf |