Skip to content

Commit 8ed775d

Browse files
authored
Data type for representing Simple polgyons using Data.Sequence and Polygons with holes (#239)
* some tests for polygons with non-empty sequences * adding holes to polygon * holes for polygons * more work on polygons with holes :) * exporitng the holes lens as well * whitespace * fixed a testcase * some instances * fix testcases * some cleaning up
1 parent f0756e2 commit 8ed775d

File tree

21 files changed

+796
-324
lines changed

21 files changed

+796
-324
lines changed

hgeometry-combinatorial/hgeometry-combinatorial.cabal

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -117,6 +117,8 @@ library
117117

118118
HGeometry.Foldable.Sort
119119
HGeometry.Foldable.Util
120+
-- HGeometry.Foldable.NonEmpty
121+
120122
HGeometry.Indexed
121123

122124
HGeometry.Lens.Util

hgeometry-combinatorial/src/HGeometry/Cyclic.hs

Lines changed: 28 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -24,6 +24,7 @@ import Control.DeepSeq (NFData)
2424
import Control.Lens
2525
import Control.Monad (forM_)
2626
import qualified Data.Foldable as F
27+
import Data.Functor.Apply (Apply, (<.*>), (<*.>), MaybeApply(..))
2728
import qualified Data.List.NonEmpty as NonEmpty
2829
import Data.Maybe (isJust)
2930
import Data.Semigroup.Foldable
@@ -33,8 +34,10 @@ import qualified Data.Vector.Mutable as MV
3334
import qualified Data.Vector.NonEmpty as NV
3435
import GHC.Generics (Generic)
3536
import HGeometry.Foldable.Util
37+
import HGeometry.Sequence.NonEmpty
3638
import HGeometry.StringSearch.KMP (isSubStringOf)
3739
import HGeometry.Vector.NonEmpty.Util ()
40+
3841
--------------------------------------------------------------------------------
3942

4043
-- | A cyclic sequence type
@@ -69,7 +72,7 @@ type instance Index (Cyclic v a) = Index (v a)
6972
type instance IxValue (Cyclic v a) = IxValue (v a)
7073

7174
instance (Index (v a) ~ Int, Foldable v, Ixed (v a)) => Ixed (Cyclic v a) where
72-
ix i = \f (Cyclic v) -> let n = F.length v
75+
ix i = \f (Cyclic v) -> let n = F.length v
7376
in Cyclic <$> ix (i `mod` n) f v
7477

7578
-- | Turn the cyclic vector into a circular Vector
@@ -105,6 +108,30 @@ instance HasDirectedTraversals NV.NonEmptyVector where
105108
n = F.length v
106109
indices' = NonEmpty.fromList [s,s-1..(s-n+1)]
107110

111+
-- | Helper to build traversal1's
112+
wrapMaybeApply :: (Indexable Int p, Apply f) => p a (f b) -> p a (MaybeApply f b)
113+
wrapMaybeApply = rmap (MaybeApply . Left)
114+
115+
116+
instance HasDirectedTraversals ViewL1 where
117+
traverseRightFrom i = \paFb xs -> let i' = i `mod` F.length xs
118+
paFb' = wrapMaybeApply paFb
119+
combine (x :<< sa) sb = x :<< (sa <> sb)
120+
in case splitL1At i' xs of
121+
Nothing -> traversed1 paFb xs
122+
Just (pref,x,suff) -> combine <$> reindexed (+i') traversed1 paFb (x :<< suff)
123+
<.*> itraversed paFb' pref
124+
125+
traverseLeftFrom i = \paFb xs ->
126+
let i' = i `mod` F.length xs
127+
paFb' = wrapMaybeApply paFb
128+
combine r1 rs = viewl1 $ r1 <>> rs
129+
in case splitL1At i' xs of
130+
Nothing -> backwards traversed1 paFb xs
131+
Just (pref,x,suff) -> combine <$> backwards traversed1 paFb (pref :>> x)
132+
<.*> backwards (reindexed (\j -> 1 + i' + j) itraversed)
133+
paFb' suff
134+
108135
-- | traverse the vector in the given order
109136
traverseByOrder :: NonEmpty.NonEmpty Int
110137
-> IndexedTraversal1' Int (NV.NonEmptyVector a) a
Lines changed: 80 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,80 @@
1+
{-# LANGUAGE UndecidableInstances #-}
2+
--------------------------------------------------------------------------------
3+
-- |
4+
-- Module : HGeometry.Polygon.Simple.Sample
5+
-- Copyright : (C) Frank Staals
6+
-- License : see the LICENSE file
7+
-- Maintainer : Frank Staals
8+
--
9+
-- Newtype to wrap some foldable structure promissing it is non-empty.
10+
--
11+
--------------------------------------------------------------------------------
12+
module HGeometry.Foldable.NonEmpty
13+
( NonEmptyF(..)
14+
) where
15+
16+
import Control.Lens
17+
import Data.Foldable1
18+
import Data.Functor.Apply (Apply, (<.*>), MaybeApply(..))
19+
import Data.Semigroup.Traversable
20+
import Data.Sequence (Seq(..))
21+
import qualified Data.Sequence as Seq
22+
import GHC.Generics (Generic)
23+
24+
--------------------------------------------------------------------------------
25+
26+
-- | We promise that the structure is non-empty
27+
newtype NonEmptyF f a = NonEmptyF (f a)
28+
deriving newtype (Functor,Foldable)
29+
deriving Generic
30+
31+
_NonEmptyF :: Iso (NonEmptyF f a) (NonEmptyF f b) (f a) (f b)
32+
_NonEmptyF = coerced
33+
34+
instance Traversable f => Traversable (NonEmptyF f) where
35+
traverse f (NonEmptyF s) = NonEmptyF <$> traverse f s
36+
37+
type instance Index (NonEmptyF f a) = Index (f a)
38+
type instance IxValue (NonEmptyF f a) = IxValue (f a)
39+
40+
instance Ixed (f a) => Ixed (NonEmptyF f a) where
41+
ix i = _NonEmptyF . ix i
42+
43+
instance Wrapped (NonEmptyF f a)
44+
45+
instance Rewrapped (NonEmptyF f a) (NonEmptyF f b)
46+
47+
instance FunctorWithIndex i f => FunctorWithIndex i (NonEmptyF f) where
48+
imap f (NonEmptyF s) = NonEmptyF $ imap f s
49+
50+
instance FoldableWithIndex i f => FoldableWithIndex i (NonEmptyF f) where
51+
ifoldMap f (NonEmptyF s) = ifoldMap f s
52+
53+
instance TraversableWithIndex i f => TraversableWithIndex i (NonEmptyF f) where
54+
itraverse f (NonEmptyF s) = NonEmptyF <$> itraverse f s
55+
56+
-- instance Foldable1 (NonEmptyF f) where
57+
-- foldMap1 = foldMap1Default
58+
59+
-- instance Traversable1 (NonEmptyF f) where
60+
-- traverse1 f (NonEmptyF s) = NonEmptyF f <$> traverse1Seq f s
61+
62+
-- instance HasFromFoldable1 (NonEmptyF f) where
63+
-- fromNonEmpty = Seq1 . fromNonEmpty
64+
65+
-- --------------------------------------------------------------------------------
66+
-- -- * Instances specific to Seq
67+
68+
-- instance Traversable1 (NonEmptyF Seq) where
69+
-- traverse1 f (NonEmptyF s) = NonEmptyF <$> traverse1Seq f s
70+
71+
-- instance Foldable1 (NonEmptyF Seq) where
72+
-- foldMap1 = foldMap1Default
73+
74+
75+
76+
-- -- | Traverse a non-empty sequence
77+
-- traverse1Seq :: Apply f => (a -> f b) -> Seq a -> f (Seq b)
78+
-- traverse1Seq f = \case
79+
-- Seq.Empty -> error "traverse1Seq: precondition violated"
80+
-- (x :<| s) -> (:<|) <$> f x <.*> traverse1Maybe f s

hgeometry-combinatorial/src/HGeometry/Sequence/NonEmpty.hs

Lines changed: 30 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -13,6 +13,9 @@ module HGeometry.Sequence.NonEmpty
1313
, viewl1, viewr1
1414
, (|>>)
1515
, (<>>)
16+
-- , (<<>)
17+
, splitL1At
18+
, splitR1At
1619
) where
1720

1821
import Control.DeepSeq
@@ -93,7 +96,6 @@ instance IsList (ViewL1 a) where
9396
fromList = maybe (error "ViewL1 fromList; empty List") fromNonEmpty . NonEmpty.nonEmpty
9497
{-# INLINE fromList #-}
9598

96-
9799
--------------------------------------------------------------------------------
98100

99101
-- | NonEmpty ViewR
@@ -166,12 +168,15 @@ instance IsList (ViewR1 a) where
166168
infixl 5 |>>
167169
infixl 5 <>>
168170

169-
-- | Append a Sequence to a ViewR
171+
-- | Append a Sequence to a ViewR1
170172
(<>>) :: ViewR1 a -> Seq a -> ViewR1 a
171173
l@(ys :>> y) <>> rs = case Sequence.viewr rs of
172174
Sequence.EmptyR -> l
173175
rs' Sequence.:> r -> (ys <> (y :<| rs')) :>> r
174176

177+
178+
179+
175180
-- | View the leftmost element
176181
viewl1 :: ViewR1 a -> ViewL1 a
177182
viewl1 (xs :>> r) = case Sequence.viewl xs of
@@ -187,6 +192,29 @@ viewr1 (l :<< ls) = case Sequence.viewr ls of
187192

188193
--------------------------------------------------------------------------------
189194

195+
-- | Given an index i, and a viewL1 s, attempts to split s at index i. Returns nothing if
196+
-- the index is out of range.
197+
splitL1At :: Int -> ViewL1 a -> Maybe (Seq a, a, Seq a)
198+
splitL1At i (x :<< s) = clampRange i (x <| s) <&> \s' -> case Sequence.splitAt i s' of
199+
(pref, y :<| suff) -> (pref, y, suff)
200+
_ -> error "splitL1At: absurd"
201+
202+
-- | Given an index i, and a viewL1 s, attempts to split s at index i. Returns nothing if
203+
-- the index is out of range.
204+
splitR1At :: Int -> ViewR1 a -> Maybe (Seq a, a, Seq a)
205+
splitR1At i (s :>> x) = clampRange i (s |> x) <&> \s' -> case Sequence.splitAt i s' of
206+
(pref, y :<| suff) -> (pref, y, suff)
207+
_ -> error "splitR1At: absurd"
208+
209+
-- | Helper to make sure the index is within range.
210+
clampRange :: Foldable t => Int -> t a -> Maybe (t a)
211+
clampRange i s
212+
| i < 0 = Nothing
213+
| i >= F.length s = Nothing
214+
| otherwise = Just s
215+
216+
--------------------------------------------------------------------------------
217+
190218

191219

192220

0 commit comments

Comments
 (0)