{-# LANGUAGE NoImplicitPrelude,RebindableSyntax #-} {-# LANGUAGE ScopedTypeVariables,FlexibleContexts #-} module Algebra.Linear ( Relation(..) , satisfies , solve , dependencies , equations , inverseImage , Matrix , Vector , matrixProduct , matrixVector , innerProduct , identity , matrixFromFunction , affine , permute , rowSwap , invert , determinant , adjoint , diagonal ) where import Auxiliary (δ,findAmong,headE,adorn) import qualified Algebra.Field import qualified Algebra.Lattice import qualified Algebra.Module import qualified Algebra.Ring import NumericPrelude import Control.Applicative ((<$>)) import Control.Arrow (first,second) import Data.List ( partition , find , transpose , genericLength , genericTake , genericDrop , genericReplicate ) import qualified Data.Map as Map import Data.Proxy (Proxy(Proxy)) import Data.Reflection (Reifies,reflect) type Vector k = [k] type Matrix k = [Vector k] -- A relation among vectors of degree 'd' over field 'k' data Relation k = Relation { getRelation :: [k] } deriving (Show) satisfies :: (Algebra.Ring.C k,Eq k) => Vector k -> Relation k -> Bool satisfies v (Relation r) = innerProduct v r == 0 -- | Calculate all dependencies among the given vectors of degree d. dependencies :: (Algebra.Field.C k,Eq k) => Integer -> [Vector k] -> [Relation k] dependencies d = map (Relation . genericDrop d) . filter (all (== zero) . genericTake d) . (\ (r,_,_) -> r) . reduce' . adorn -- | Calculate the equations satisfied by the subspace spanned by the given vectors of degree d. equations :: (Algebra.Field.C k,Eq k) => Integer -> [Vector k] -> [Relation k] equations d vs = dependencies (genericLength vs + 1) . transpose . (:) (genericReplicate d zero) $ vs -- | Solve the given equations, in the form of a basis of vectors of degree d. solve :: (Algebra.Field.C k,Eq k) => Integer -> [Relation k] -> [Vector k] solve d = map getRelation . equations d . map getRelation inverseImage :: (Algebra.Field.C k,Eq k) => Matrix k -> Vector k -> Vector k inverseImage a = solveUpperTriangular u . matrixVector b where (u,b,_) = reduce' a invert :: (Algebra.Field.C k,Eq k) => Matrix k -> Maybe (Matrix k) invert m = fmap strip . process . (\ (r,_,_) -> r) . reduce' . adorn $ m where n = length m process x = go x where go [v] = Just [v] go (r@(pivot : r') : rest) | pivot == 1 = do m' <- go (map tail rest) rowsToAdd <- sequence . zipWith3 f [0 ..] r' $ m' return $ (1 : foldr (zipWith (+)) r' rowsToAdd) : map (0 :) m' | otherwise = Nothing f i c v | v₀ == 0 = Nothing | otherwise = Just $ map ((*) (negate c / v₀)) v where v₀ = v !! i strip = map (drop n) determinant :: (Algebra.Field.C k,Eq k,DebugDeterminant k) => Matrix k -> k determinant x = case reduce x of (_,_,σ) -> σ adjoint :: (Algebra.Lattice.C k,Algebra.Field.C k,Eq k,DebugDeterminant k) => Matrix k -> Maybe (Matrix k) adjoint a = (abs (determinant a) *>) <$> invert a diagonal :: Matrix k -> [k] diagonal [] = [] diagonal ((d : _) : rest) = d : diagonal (map tail rest) matrixProduct :: (Algebra.Ring.C k) => Matrix k -> Matrix k -> Matrix k matrixProduct a b = map (($ transpose b) . map . innerProduct) a matrixVector :: (Algebra.Ring.C k) => Matrix k -> Vector k -> Vector k matrixVector a = map (\ [x] -> x) . matrixProduct a . map (: []) innerProduct :: (Algebra.Ring.C k) => Vector k -> Vector k -> k innerProduct a b = sum (zipWith (*) a b) matrixFromFunction :: Int -> Int -> (Int -> Int -> k) -> Matrix k matrixFromFunction m n f = [[f i j | j <- [1 .. n]] | i <- [1 .. m]] identity :: (Algebra.Ring.C k) => Int -> Matrix k identity n = matrixFromFunction n n δ -- Triangular decomposition solveUpperTriangular :: (Algebra.Field.C k,Eq k) => Matrix k -> Vector k -> Vector k solveUpperTriangular u x = reverse $ solveLowerTriangular (reverse . map reverse $ u) (reverse x) solveLowerTriangular :: (Algebra.Field.C k,Eq k) => Matrix k -> Vector k -> Vector k solveLowerTriangular l x = go l x [] where go [] [] q = q go (lᵢ : l') (xᵢ : x') q = go l' x' (q ++ [qᵢ]) where (lFirst,lᵢᵢ : _) = splitAt (length q) lᵢ y = xᵢ - innerProduct q lFirst qᵢ | lᵢᵢ == 0 = error "Linear.solveLowerTriangular: zero on diagonal" | otherwise = y / lᵢᵢ class DebugDeterminant a where reduce :: (Algebra.Field.C k,Eq k,DebugDeterminant k) => Matrix k -> (Matrix k,Matrix k,k) reduce = reduce' -- Compute the row echelon form of the matrix, -- together with the basis transformation matrix, -- and its determinant. reduce' :: (Algebra.Field.C k,Eq k) => Matrix k -> (Matrix k,Matrix k,k) reduce' [] = ([],[],1) reduce' xs@([] : _) = (xs,identity (length xs),1) reduce' vs = case nonZero of [] -> (\ (x,u,_σ) -> (map (0 :) x,u,0)) $ reduce' (map tail vs) (v@(v₀ : _),i) : [] -> let subMatrix = map (tail . fst) startZero (h,u,σ) = reduce' subMatrix sign = if odd i then 1 else -1 in ( (map (/ v₀) v :) . map (0 :) $ h , normalisation v₀ `matrixProduct` rowSwap n (1,i) `matrixProduct` shift u ,sign * v₀ * σ ) (v@(v₀ : _),i) : rest -> let (reduced,translates) = unzip . flip map rest $ \ (x@(x₀ : _),j) -> let c = x₀ / v₀ in ((zipWith (\ vᵢ xᵢ -> xᵢ - c * vᵢ) v x,j),(j,c)) subMatrix = v : map fst reduced ++ map fst startZero (h,u,σ) = reduce' subMatrix permutation = i : map snd reduced ++ map snd startZero in ( h , u `matrixProduct` permute permutation `matrixProduct` affine n i (map (second negate) translates) , permutationSign permutation * σ ) where (startZero,nonZero) = partition ((==) 0 . head . fst) . flip zip [1 ..] $ vs normalisation v₀ = matrixFromFunction n n f where f 1 1 = 1 / v₀ f i j = δ i j shift u = (1 : replicate (n - 1) 0) : map (0 :) u n = length vs rowSwap :: (Algebra.Ring.C k) => Int -> (Int,Int) -> Matrix k rowSwap n (k,l) = matrixFromFunction n n f where f i j | i == k && j == l = one | i == l && j == k = one | i == j && i /= k && i /= l = one | otherwise = zero affine :: (Algebra.Ring.C k) => Int -> Int -> [(Int,k)] -> Matrix k affine n k ps = matrixFromFunction n n $ \ i j -> δ i j + c i j where m = Map.fromList ps c i j = case (Map.lookup i m,j == k) of (Just cᵢ,True) -> cᵢ _ -> zero permute :: (Algebra.Ring.C k) => [Int] -> Matrix k permute is = matrixFromFunction n n (\ i j -> δ (is !! (i - 1)) j) where n = length is permutationSign :: (Algebra.Ring.C k) => [Int] -> k permutationSign [] = one permutationSign (x : xs) = ε * permutationSign xs where inversions = length $ filter (x >) xs ε | even inversions = one | otherwise = negate one -- Example x :: Matrix Rational x = [ [0, 3,-6, 6,4,5 ] , [3,-7, 8,-5,8,9 ] , [3,-9,12,-9,6,15] ] _M₁,_M₂,_M₃ :: Matrix Rational _M₁ = [ [0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,-108221942156800 % 524799,0 % 1,0 % 1,108221942156800 % 524799,0 % 1,1 % 1] , [-169096784620000 % 453365147813277,-838720051715200 % 4987016625946047,6763871384800 % 151121715937759,216443884313600 % 4987016625946047,392304540318400 % 4987016625946047,27055485539200 % 1662338875315349,351721312009600 % 453365147813277,1975050444361600 % 4987016625946047,101458070772000 % 1662338875315349,5221708709065600 % 4987016625946047,1102511035722400 % 4987016625946047,1 % 1] , [0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,-541109710784 % 95367421875,0 % 1,0 % 1,0 % 1,541109710784 % 95367421875,1 % 1] , [0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,6763871384800 % 16663069252269,0 % 1,0 % 1,1 % 1] , [0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,211370980775 % 536346624,0 % 1,0 % 1,0 % 1,1 % 1] , [3381935692400 % 19061697322899,-3381935692400 % 19061697322899,-3381935692400 % 19061697322899,0 % 1,0 % 1,3381935692400 % 19061697322899,3381935692400 % 19061697322899,0 % 1,0 % 1,-3381935692400 % 19061697322899,0 % 1,1 % 1] , [0 % 1,-211370980775 % 537394176,0 % 1,211370980775 % 537394176,0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,-211370980775 % 537394176,0 % 1,1 % 1] , [-3381935692400 % 36321901,0 % 1,3381935692400 % 36321901,0 % 1,0 % 1,0 % 1,-3381935692400 % 36321901,0 % 1,0 % 1,0 % 1,0 % 1,1 % 1] , [-108221942156800 % 524799,108221942156800 % 524799,0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,1 % 1] , [108221942156800 % 1,0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,1 % 1] , [0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,1 % 1] , [108221942156800 % 1,0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,1 % 1] ] _M₂ = [ [0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,-108221942156800 % 524799,0 % 1,0 % 1,108221942156800 % 524799,0 % 1,1 % 1] , [-169096784620000 % 453365147813277,-838720051715200 % 4987016625946047,6763871384800 % 151121715937759,216443884313600 % 4987016625946047,392304540318400 % 4987016625946047,27055485539200 % 1662338875315349,351721312009600 % 453365147813277,1975050444361600 % 4987016625946047,101458070772000 % 1662338875315349,5221708709065600 % 4987016625946047,1102511035722400 % 4987016625946047,1 % 1] , [0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,-541109710784 % 95367421875,0 % 1,0 % 1,0 % 1,541109710784 % 95367421875,1 % 1] , [0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,6763871384800 % 16663069252269,0 % 1,0 % 1,1 % 1] , [0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,211370980775 % 536346624,0 % 1,0 % 1,0 % 1,1 % 1] , [3381935692400 % 19061697322899,-3381935692400 % 19061697322899,-3381935692400 % 19061697322899,0 % 1,0 % 1,3381935692400 % 19061697322899,3381935692400 % 19061697322899,0 % 1,0 % 1,-3381935692400 % 19061697322899,0 % 1,1 % 1] , [0 % 1,-211370980775 % 537394176,0 % 1,211370980775 % 537394176,0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,-211370980775 % 537394176,0 % 1,1 % 1] , [-3381935692400 % 36321901,0 % 1,3381935692400 % 36321901,0 % 1,0 % 1,0 % 1,-3381935692400 % 36321901,0 % 1,0 % 1,0 % 1,0 % 1,1 % 1] , [-108221942156800 % 524799,108221942156800 % 524799,0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,1 % 1] , [108221942156800 % 1,0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,1 % 1] , [0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,1 % 1] , [0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,108221942156800 % 1,0 % 1,0 % 1,0 % 1,0 % 1,1 % 1] ] _M₃ = [ [0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,-108221942156800 % 524799,0 % 1,0 % 1,108221942156800 % 524799,0 % 1,1 % 1] , [-169096784620000 % 453365147813277,-838720051715200 % 4987016625946047,6763871384800 % 151121715937759,216443884313600 % 4987016625946047,392304540318400 % 4987016625946047,27055485539200 % 1662338875315349,351721312009600 % 453365147813277,1975050444361600 % 4987016625946047,101458070772000 % 1662338875315349,5221708709065600 % 4987016625946047,1102511035722400 % 4987016625946047,1 % 1] , [0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,-541109710784 % 95367421875,0 % 1,0 % 1,0 % 1,541109710784 % 95367421875,1 % 1] , [0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,6763871384800 % 16663069252269,0 % 1,0 % 1,1 % 1] , [0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,211370980775 % 536346624,0 % 1,0 % 1,0 % 1,1 % 1] , [3381935692400 % 19061697322899,-3381935692400 % 19061697322899,-3381935692400 % 19061697322899,0 % 1,0 % 1,3381935692400 % 19061697322899,3381935692400 % 19061697322899,0 % 1,0 % 1,-3381935692400 % 19061697322899,0 % 1,1 % 1] , [0 % 1,-211370980775 % 537394176,0 % 1,211370980775 % 537394176,0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,-211370980775 % 537394176,0 % 1,1 % 1] , [-3381935692400 % 36321901,0 % 1,3381935692400 % 36321901,0 % 1,0 % 1,0 % 1,-3381935692400 % 36321901,0 % 1,0 % 1,0 % 1,0 % 1,1 % 1] , [-108221942156800 % 524799,108221942156800 % 524799,0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,1 % 1] , [108221942156800 % 1,0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,1 % 1] , [0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,1 % 1] , [54110971078400 % 1,0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,54110971078400 % 1,0 % 1,0 % 1,0 % 1,0 % 1,1 % 1] ] d₁,d₂,d₃ :: Rational d₁ = 0 % 1 d₂ = 2399533449150898860018929580106057857312831592024080652407697547921113137254208406108697383229906184194039925435269120000000000000 % 10384619707704007440069688317960727557546629554588436333459508359228638653867 d₃ = -1199766724575449430009464790053028928656415796012040326203848773960556568627104203054348691614953092097019962717634560000000000000 % 10384619707704007440069688317960727557546629554588436333459508359228638653867 test1,test2,test3,test4,test5,test7,test8 :: Matrix Rational test1 = [[-169096784620000 % 453365147813277,-838720051715200 % 4987016625946047,6763871384800 % 151121715937759,216443884313600 % 4987016625946047,392304540318400 % 4987016625946047,27055485539200 % 1662338875315349,351721312009600 % 453365147813277,1975050444361600 % 4987016625946047,101458070772000 % 1662338875315349,5221708709065600 % 4987016625946047,1102511035722400 % 4987016625946047,1 % 1],[0 % 1,-135277427696 % 525510452511,-270554855392 % 1732881574809,4328877686272 % 209678670551889,7846090806368 % 209678670551889,5546374535536 % 29954095793127,135277427696 % 247554510687,39501008887232 % 209678670551889,676387138480 % 23297630061321,9604697366416 % 29954095793127,22050220714448 % 209678670551889,66973810188487 % 45384993625950],[0 % 1,16774401034304 % 399540911,270554855392 % 3301991,-4328877686272 % 399540911,-7846090806368 % 399540911,-1623329132352 % 399540911,-135277427696 % 471713,-39501008887232 % 399540911,-6087484246320 % 399540911,-104434174181312 % 399540911,-22050220714448 % 399540911,-64766190245461 % 259442150],[0 % 1,30302143803904 % 101277,-4328877686272 % 174933,-138524085960704 % 5772789,-251074905803776 % 5772789,-17315510745088 % 1924263,-225101639686144 % 524799,-1264032284391424 % 5772789,-21644388431360 % 641421,-3341893573801984 % 5772789,-705607062862336 % 5772789,-2417947450630819 % 4373325],[0 % 1,-536780833097728 % 11,12986633058816 % 1,138524085960704 % 11,251074905803776 % 11,51946532235264 % 11,225101639686144 % 1,1264032284391424 % 11,194799495882240 % 11,3341893573801984 % 11,705607062862336 % 11,7253842365012457 % 25],[0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,-108221942156800 % 524799,0 % 1,0 % 1,108221942156800 % 524799,0 % 1,1 % 1],[0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,-541109710784 % 95367421875,0 % 1,0 % 1,0 % 1,541109710784 % 95367421875,1 % 1],[0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,6763871384800 % 16663069252269,0 % 1,0 % 1,1 % 1],[0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,211370980775 % 536346624,0 % 1,0 % 1,0 % 1,1 % 1],[0 % 1,-211370980775 % 537394176,0 % 1,211370980775 % 537394176,0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,-211370980775 % 537394176,0 % 1,1 % 1],[0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,1 % 1],[0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,108221942156800 % 1,0 % 1,0 % 1,0 % 1,0 % 1,1 % 1]] test2 = [[-135277427696 % 525510452511,-270554855392 % 1732881574809,4328877686272 % 209678670551889,7846090806368 % 209678670551889,5546374535536 % 29954095793127,135277427696 % 247554510687,39501008887232 % 209678670551889,676387138480 % 23297630061321,9604697366416 % 29954095793127,22050220714448 % 209678670551889,66973810188487 % 45384993625950],[0 % 1,6763871384800 % 119772219,-108221942156800 % 14492438499,-196152270159200 % 14492438499,54110971078400 % 2070348357,-3381935692400 % 17110317,-987525222180800 % 14492438499,-50729035386000 % 4830812833,-432887768627200 % 2070348357,-551255517861200 % 14492438499,-1124184870087 % 125475658],[0 % 1,-108221942156800 % 524799,0 % 1,0 % 1,108221942156800 % 524799,108221942156800 % 524799,0 % 1,0 % 1,-108221942156800 % 524799,0 % 1,1162300833 % 1],[0 % 1,16990844918617600 % 399,3463102149017600 % 399,6276872645094400 % 399,-1731551074508800 % 57,6926204298035200 % 57,31600807109785600 % 399,1623329132352000 % 133,13852408596070400 % 57,17640176571558400 % 399,197878620851139 % 19],[0 % 1,2325080788525 % 9746376192,77573149944425 % 214420276224,-6129758442475 % 107210138112,-8666210211775 % 30631468032,-2325080788525 % 2784678912,-15430081596575 % 53605069056,-1056854903875 % 23824475136,-211370980775 % 239308344,-34453469866325 % 214420276224,-66944106946759 % 29703241728],[0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,-108221942156800 % 524799,0 % 1,0 % 1,108221942156800 % 524799,0 % 1,1 % 1],[0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,-541109710784 % 95367421875,0 % 1,0 % 1,0 % 1,541109710784 % 95367421875,1 % 1],[0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,6763871384800 % 16663069252269,0 % 1,0 % 1,1 % 1],[0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,211370980775 % 536346624,0 % 1,0 % 1,0 % 1,1 % 1],[0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,1 % 1],[0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,108221942156800 % 1,0 % 1,0 % 1,0 % 1,0 % 1,1 % 1]] test3 = [[6763871384800 % 119772219,-108221942156800 % 14492438499,-196152270159200 % 14492438499,54110971078400 % 2070348357,-3381935692400 % 17110317,-987525222180800 % 14492438499,-50729035386000 % 4830812833,-432887768627200 % 2070348357,-551255517861200 % 14492438499,-1124184870087 % 125475658],[0 % 1,-1731551074508800 % 63500679,-3138436322547200 % 63500679,6385094587251200 % 21166893,-270554855392000 % 524799,-15800403554892800 % 63500679,-270554855392000 % 7055631,-61578285087219200 % 63500679,-8820088285779200 % 63500679,724539378362069 % 641421],[0 % 1,1731551074508800 % 121,3138436322547200 % 121,-6060428760780800 % 121,270554855392000 % 1,15800403554892800 % 121,2434993698528000 % 121,48483430086246400 % 121,8820088285779200 % 121,188875843483779 % 11],[0 % 1,211370980775 % 537394176,0 % 1,-211370980775 % 537394176,0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,-178053373 % 80352],[0 % 1,0 % 1,0 % 1,0 % 1,-108221942156800 % 524799,0 % 1,0 % 1,108221942156800 % 524799,0 % 1,1 % 1],[0 % 1,0 % 1,0 % 1,0 % 1,-541109710784 % 95367421875,0 % 1,0 % 1,0 % 1,541109710784 % 95367421875,1 % 1],[0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,6763871384800 % 16663069252269,0 % 1,0 % 1,1 % 1],[0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,211370980775 % 536346624,0 % 1,0 % 1,0 % 1,1 % 1],[0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,1 % 1],[0 % 1,0 % 1,0 % 1,0 % 1,108221942156800 % 1,0 % 1,0 % 1,0 % 1,0 % 1,1 % 1]] test4 = [[-1731551074508800 % 63500679,-3138436322547200 % 63500679,6385094587251200 % 21166893,-270554855392000 % 524799,-15800403554892800 % 63500679,-270554855392000 % 7055631,-61578285087219200 % 63500679,-8820088285779200 % 63500679,724539378362069 % 641421],[0 % 1,0 % 1,108221942156800 % 1,0 % 1,0 % 1,0 % 1,-108221942156800 % 1,0 % 1,609975477158400 % 1],[0 % 1,-6129758442475 % 8598306816,34030727904775 % 8598306816,-11625403942625 % 1563328512,-15430081596575 % 4299153408,-1056854903875 % 1910734848,-120270088060975 % 8598306816,-34453469866325 % 17196613632,5634017560436093 % 400212099072],[0 % 1,0 % 1,0 % 1,-108221942156800 % 524799,0 % 1,0 % 1,108221942156800 % 524799,0 % 1,1 % 1],[0 % 1,0 % 1,0 % 1,-541109710784 % 95367421875,0 % 1,0 % 1,0 % 1,541109710784 % 95367421875,1 % 1],[0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,6763871384800 % 16663069252269,0 % 1,0 % 1,1 % 1],[0 % 1,0 % 1,0 % 1,0 % 1,211370980775 % 536346624,0 % 1,0 % 1,0 % 1,1 % 1],[0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,1 % 1],[0 % 1,0 % 1,0 % 1,108221942156800 % 1,0 % 1,0 % 1,0 % 1,0 % 1,1 % 1]] test5 = [[-108221942156800 % 524799,0 % 1,0 % 1,108221942156800 % 524799,0 % 1,1 % 1],[0 % 1,0 % 1,0 % 1,-541109710784 % 95367421875,541109710784 % 95367421875,577984359097 % 577984375000],[0 % 1,0 % 1,0 % 1,108221942156800 % 1,0 % 1,524800 % 1],[0 % 1,0 % 1,6763871384800 % 16663069252269,0 % 1,0 % 1,1 % 1],[0 % 1,211370980775 % 536346624,0 % 1,0 % 1,0 % 1,1 % 1],[0 % 1,0 % 1,0 % 1,0 % 1,0 % 1,1 % 1]] test7 = [[0 % 1,-541109710784 % 95367421875,541109710784 % 95367421875,577984359097 % 577984375000],[0 % 1,108221942156800 % 1,0 % 1,524800 % 1],[6763871384800 % 16663069252269,0 % 1,0 % 1,1 % 1],[0 % 1,0 % 1,0 % 1,1 % 1]] test8 = [[-541109710784 % 95367421875,541109710784 % 95367421875,577984359097 % 577984375000],[108221942156800 % 1,0 % 1,524800 % 1],[0 % 1,0 % 1,1 % 1]]