Merge VectorTypes.hs into Vector.hs
This commit is contained in:
parent
9d6af63b46
commit
3c1a34e4af
@ -2,7 +2,6 @@
|
||||
|
||||
module Algebra.Vector where
|
||||
|
||||
import Algebra.VectorTypes
|
||||
import Control.Applicative
|
||||
import Data.List (sortBy)
|
||||
import Diagrams.TwoD.Types
|
||||
@ -11,6 +10,19 @@ import GHC.Float
|
||||
import MyPrelude
|
||||
|
||||
|
||||
type Vec = R2
|
||||
type PT = P2
|
||||
type Coord = (Double, Double)
|
||||
type Segment = (PT, PT)
|
||||
type Square = (Coord, Coord)
|
||||
|
||||
|
||||
data Alignment = CW
|
||||
| CCW
|
||||
| CL
|
||||
deriving (Eq)
|
||||
|
||||
|
||||
-- |Checks whether the Point is in a given dimension.
|
||||
inRange :: Square -- ^ the square: ((xmin, xmax), (ymin, ymax))
|
||||
-> PT -- ^ Coordinate
|
||||
|
@ -1,18 +0,0 @@
|
||||
{-# OPTIONS_HADDOCK ignore-exports #-}
|
||||
|
||||
module Algebra.VectorTypes where
|
||||
|
||||
import Diagrams.TwoD.Types
|
||||
|
||||
|
||||
type Vec = R2
|
||||
type PT = P2
|
||||
type Coord = (Double, Double)
|
||||
type Segment = (PT, PT)
|
||||
type Square = (Coord, Coord)
|
||||
|
||||
|
||||
data Alignment = CW
|
||||
| CCW
|
||||
| CL
|
||||
deriving (Eq)
|
@ -3,7 +3,6 @@
|
||||
module Algorithms.GrahamScan where
|
||||
|
||||
import Algebra.Vector
|
||||
import Algebra.VectorTypes
|
||||
import MyPrelude
|
||||
|
||||
|
||||
|
@ -16,7 +16,6 @@ module Algorithms.KDTree (kdTree
|
||||
where
|
||||
|
||||
|
||||
import Algebra.VectorTypes
|
||||
import Algebra.Vector
|
||||
import Data.Maybe (fromJust, catMaybes)
|
||||
import Data.Tree
|
||||
|
@ -2,7 +2,6 @@ module Algorithms.PolygonIntersection where
|
||||
|
||||
|
||||
import Algebra.Vector
|
||||
import Algebra.VectorTypes
|
||||
import Control.Applicative
|
||||
import Data.Dequeue (BankersDequeue)
|
||||
import qualified Data.Dequeue as Q
|
||||
|
@ -16,7 +16,6 @@ module Algorithms.QuadTree
|
||||
QTZipper)
|
||||
where
|
||||
|
||||
import Algebra.VectorTypes
|
||||
import Algebra.Vector
|
||||
import Data.Foldable (foldlM)
|
||||
import Data.List (partition)
|
||||
|
@ -2,7 +2,6 @@
|
||||
|
||||
module Graphics.Diagram.Gif where
|
||||
|
||||
import Algebra.VectorTypes
|
||||
import Algorithms.GrahamScan
|
||||
import Codec.Picture.Gif
|
||||
import qualified Data.ByteString.Char8 as B
|
||||
|
@ -2,7 +2,7 @@
|
||||
|
||||
module Graphics.Diagram.Plotter where
|
||||
|
||||
import Algebra.VectorTypes
|
||||
import Algebra.Vector(PT,Square)
|
||||
import Algorithms.GrahamScan
|
||||
import Algorithms.QuadTree
|
||||
import Algorithms.KDTree
|
||||
|
@ -3,7 +3,6 @@
|
||||
module Graphics.Diagram.Types where
|
||||
|
||||
import Algebra.Vector
|
||||
import Algebra.VectorTypes
|
||||
import Diagrams.Backend.Cairo
|
||||
import Diagrams.Prelude
|
||||
import MyPrelude
|
||||
|
@ -2,7 +2,7 @@
|
||||
|
||||
module Parser.Meshparser (meshToArr, facesToArr) where
|
||||
|
||||
import Algebra.VectorTypes
|
||||
import Algebra.Vector(PT)
|
||||
import Control.Applicative
|
||||
import Data.Attoparsec.ByteString.Char8
|
||||
import Data.Either
|
||||
|
Loading…
Reference in New Issue
Block a user