Restructure Algorithms subdir and module names

No subdirs in Algorithms, just the module files
This commit is contained in:
hasufell 2014-12-03 21:26:35 +01:00
parent f1f3f20a26
commit 73e1673c63
No known key found for this signature in database
GPG Key ID: 220CD1C5BDEED020
15 changed files with 31 additions and 31 deletions

View File

@ -1,6 +1,6 @@
{-# OPTIONS_HADDOCK ignore-exports #-} {-# OPTIONS_HADDOCK ignore-exports #-}
module Algorithms.ConvexHull.GrahamScan where module Algorithms.GrahamScan where
import Algebra.Vector import Algebra.Vector
import Algebra.VectorTypes import Algebra.VectorTypes

View File

@ -1,18 +1,18 @@
{-# OPTIONS_HADDOCK ignore-exports #-} {-# OPTIONS_HADDOCK ignore-exports #-}
module Algorithms.KDTree.KDTree (kdTree module Algorithms.KDTree (kdTree
, kdFoldl , kdFoldl
, kdFoldr , kdFoldr
, kdTreeToRoseTree , kdTreeToRoseTree
, rangeSearch , rangeSearch
, getValS , getValS
, isLeaf , isLeaf
, getVal , getVal
, getDirection , getDirection
, goLeft , goLeft
, goRight , goRight
, Direction(Vertical, Horizontal) , Direction(Vertical, Horizontal)
, KDTree(KTNil, KTNode)) , KDTree(KTNil, KTNode))
where where

View File

@ -1,4 +1,4 @@
module Algorithms.PolygonIntersection.Core where module Algorithms.PolygonIntersection where
import Algebra.Vector import Algebra.Vector

View File

@ -1,4 +1,4 @@
module Algorithms.QuadTree.QuadTree module Algorithms.QuadTree
(quadTree, (quadTree,
quadTreeSquares, quadTreeSquares,
qtFoldl, qtFoldl,

View File

@ -55,10 +55,10 @@ executable Gtk
-- Modules included in this executable, other than Main. -- Modules included in this executable, other than Main.
other-modules: Algebra.Vector other-modules: Algebra.Vector
Algorithms.ConvexHull.GrahamScan Algorithms.GrahamScan
Algorithms.PolygonIntersection.Core Algorithms.PolygonIntersection
Algorithms.QuadTree.QuadTree Algorithms.QuadTree
Algorithms.KDTree.KDTree Algorithms.KDTree
Graphics.Diagram.Gtk Graphics.Diagram.Gtk
Graphics.Diagram.Plotter Graphics.Diagram.Plotter
Graphics.Diagram.Types Graphics.Diagram.Types
@ -102,10 +102,10 @@ executable Gif
-- Modules included in this executable, other than Main. -- Modules included in this executable, other than Main.
other-modules: Algebra.Vector other-modules: Algebra.Vector
Algorithms.ConvexHull.GrahamScan Algorithms.GrahamScan
Algorithms.PolygonIntersection.Core Algorithms.PolygonIntersection
Algorithms.QuadTree.QuadTree Algorithms.QuadTree
Algorithms.KDTree.KDTree Algorithms.KDTree
Graphics.Diagram.Gif Graphics.Diagram.Gif
Graphics.Diagram.Plotter Graphics.Diagram.Plotter
Graphics.Diagram.Types Graphics.Diagram.Types

View File

@ -3,7 +3,7 @@
module Graphics.Diagram.Gif where module Graphics.Diagram.Gif where
import Algebra.VectorTypes import Algebra.VectorTypes
import Algorithms.ConvexHull.GrahamScan import Algorithms.GrahamScan
import Codec.Picture.Gif import Codec.Picture.Gif
import qualified Data.ByteString.Char8 as B import qualified Data.ByteString.Char8 as B
import Data.Monoid import Data.Monoid

View File

@ -3,10 +3,10 @@
module Graphics.Diagram.Plotter where module Graphics.Diagram.Plotter where
import Algebra.VectorTypes import Algebra.VectorTypes
import Algorithms.ConvexHull.GrahamScan import Algorithms.GrahamScan
import Algorithms.QuadTree.QuadTree import Algorithms.QuadTree
import Algorithms.KDTree.KDTree import Algorithms.KDTree
import Algorithms.PolygonIntersection.Core import Algorithms.PolygonIntersection
import Data.Maybe import Data.Maybe
import Data.Monoid import Data.Monoid
import Data.Tree import Data.Tree

View File

@ -2,7 +2,7 @@
module Parser.PathParser where module Parser.PathParser where
import Algorithms.QuadTree.QuadTree (Quad(NW, NE, SW, SE), Orient(North, South, West, East)) import Algorithms.QuadTree (Quad(NW, NE, SW, SE), Orient(North, South, West, East))
import Control.Applicative import Control.Applicative
import Data.Attoparsec.ByteString.Char8 import Data.Attoparsec.ByteString.Char8
import qualified Data.ByteString.Char8 as B import qualified Data.ByteString.Char8 as B

View File

@ -1,4 +1,4 @@
import Algorithms.ConvexHull.GrahamScan import Algorithms.GrahamScan
import Parser.Meshparser import Parser.Meshparser
import System.Environment import System.Environment
import System.FileSystem.FileExt import System.FileSystem.FileExt