]> gitweb.michael.orlitzky.com - spline3.git/commitdiff
Import cleanup in Tetrahedron.
authorMichael Orlitzky <michael@orlitzky.com>
Thu, 16 Apr 2015 01:37:08 +0000 (21:37 -0400)
committerMichael Orlitzky <michael@orlitzky.com>
Thu, 16 Apr 2015 01:37:08 +0000 (21:37 -0400)
src/Tetrahedron.hs

index 0e2f9029dd80f9c42b32a8779cbcf40cf50c6df2..8e9acd38c8b9a0b858f56287fc8aa0c637fd8beb 100644 (file)
@@ -1,4 +1,5 @@
 {-# LANGUAGE BangPatterns #-}
+
 module Tetrahedron (
   Tetrahedron(..),
   b0, -- Cube test
@@ -10,27 +11,22 @@ module Tetrahedron (
   polynomial,
   tetrahedron_properties,
   tetrahedron_tests,
-  volume -- Cube test
-  )
+  volume ) -- Cube test
 where
 
-import qualified Data.Vector as V (
-  singleton,
-  snoc,
-  sum
-  )
-
-import Test.Framework (Test, testGroup)
-import Test.Framework.Providers.HUnit (testCase)
-import Test.Framework.Providers.QuickCheck2 (testProperty)
+import Data.Vector ( singleton, snoc )
+import qualified Data.Vector as V ( sum )
+import Test.Framework ( Test, testGroup )
+import Test.Framework.Providers.HUnit ( testCase )
+import Test.Framework.Providers.QuickCheck2 ( testProperty )
 import Test.HUnit (Assertion, assertEqual)
-import Test.QuickCheck (Arbitrary(..), Gen, Property, (==>))
+import Test.QuickCheck ( Arbitrary(..), Gen, Property, (==>) )
 
-import Comparisons ((~=))
-import FunctionValues (FunctionValues(..), empty_values)
-import Misc (factorial)
-import Point (Point(..), scale)
-import RealFunction (RealFunction, cmult, fexp)
+import Comparisons ( (~=) )
+import FunctionValues ( FunctionValues(..), empty_values )
+import Misc ( factorial )
+import Point ( Point(..), scale )
+import RealFunction ( RealFunction, cmult, fexp )
 
 data Tetrahedron =
   Tetrahedron { function_values :: FunctionValues,
@@ -78,25 +74,25 @@ barycenter (Tetrahedron _ v0' v1' v2' v3' _) =
 {-# INLINE polynomial #-}
 polynomial :: Tetrahedron -> (RealFunction Point)
 polynomial t =
-    V.sum $ V.singleton ((c t 0 0 0 3) `cmult` (beta t 0 0 0 3)) `V.snoc`
-            ((c t 0 0 1 2) `cmult` (beta t 0 0 1 2)) `V.snoc`
-            ((c t 0 0 2 1) `cmult` (beta t 0 0 2 1)) `V.snoc`
-            ((c t 0 0 3 0) `cmult` (beta t 0 0 3 0)) `V.snoc`
-            ((c t 0 1 0 2) `cmult` (beta t 0 1 0 2)) `V.snoc`
-            ((c t 0 1 1 1) `cmult` (beta t 0 1 1 1)) `V.snoc`
-            ((c t 0 1 2 0) `cmult` (beta t 0 1 2 0)) `V.snoc`
-            ((c t 0 2 0 1) `cmult` (beta t 0 2 0 1)) `V.snoc`
-            ((c t 0 2 1 0) `cmult` (beta t 0 2 1 0)) `V.snoc`
-            ((c t 0 3 0 0) `cmult` (beta t 0 3 0 0)) `V.snoc`
-            ((c t 1 0 0 2) `cmult` (beta t 1 0 0 2)) `V.snoc`
-            ((c t 1 0 1 1) `cmult` (beta t 1 0 1 1)) `V.snoc`
-            ((c t 1 0 2 0) `cmult` (beta t 1 0 2 0)) `V.snoc`
-            ((c t 1 1 0 1) `cmult` (beta t 1 1 0 1)) `V.snoc`
-            ((c t 1 1 1 0) `cmult` (beta t 1 1 1 0)) `V.snoc`
-            ((c t 1 2 0 0) `cmult` (beta t 1 2 0 0)) `V.snoc`
-            ((c t 2 0 0 1) `cmult` (beta t 2 0 0 1)) `V.snoc`
-            ((c t 2 0 1 0) `cmult` (beta t 2 0 1 0)) `V.snoc`
-            ((c t 2 1 0 0) `cmult` (beta t 2 1 0 0)) `V.snoc`
+    V.sum $ singleton ((c t 0 0 0 3) `cmult` (beta t 0 0 0 3)) `snoc`
+            ((c t 0 0 1 2) `cmult` (beta t 0 0 1 2)) `snoc`
+            ((c t 0 0 2 1) `cmult` (beta t 0 0 2 1)) `snoc`
+            ((c t 0 0 3 0) `cmult` (beta t 0 0 3 0)) `snoc`
+            ((c t 0 1 0 2) `cmult` (beta t 0 1 0 2)) `snoc`
+            ((c t 0 1 1 1) `cmult` (beta t 0 1 1 1)) `snoc`
+            ((c t 0 1 2 0) `cmult` (beta t 0 1 2 0)) `snoc`
+            ((c t 0 2 0 1) `cmult` (beta t 0 2 0 1)) `snoc`
+            ((c t 0 2 1 0) `cmult` (beta t 0 2 1 0)) `snoc`
+            ((c t 0 3 0 0) `cmult` (beta t 0 3 0 0)) `snoc`
+            ((c t 1 0 0 2) `cmult` (beta t 1 0 0 2)) `snoc`
+            ((c t 1 0 1 1) `cmult` (beta t 1 0 1 1)) `snoc`
+            ((c t 1 0 2 0) `cmult` (beta t 1 0 2 0)) `snoc`
+            ((c t 1 1 0 1) `cmult` (beta t 1 1 0 1)) `snoc`
+            ((c t 1 1 1 0) `cmult` (beta t 1 1 1 0)) `snoc`
+            ((c t 1 2 0 0) `cmult` (beta t 1 2 0 0)) `snoc`
+            ((c t 2 0 0 1) `cmult` (beta t 2 0 0 1)) `snoc`
+            ((c t 2 0 1 0) `cmult` (beta t 2 0 1 0)) `snoc`
+            ((c t 2 1 0 0) `cmult` (beta t 2 1 0 0)) `snoc`
             ((c t 3 0 0 0) `cmult` (beta t 3 0 0 0))