geojson-4.0.2: A thin GeoJSON Layer above the aeson library

Copyright(C) 2014-2019 HS-GeoJSON Project
LicenseBSD-style (see the file LICENSE.md)
MaintainerAndrew Newman
Safe HaskellNone
LanguageHaskell2010

Data.LinearRing

Contents

Description

Refer to the GeoJSON Spec http://geojson.org/geojson-spec.html#polygon

A LinearRing is a List with at least 4 elements, where the first element is expected to be the same as the last.

Synopsis

Type

data LinearRing a Source #

a LinearRing has at least 3 (distinct) elements

Instances
Functor LinearRing Source # 
Instance details

Defined in Data.LinearRing

Methods

fmap :: (a -> b) -> LinearRing a -> LinearRing b #

(<$) :: a -> LinearRing b -> LinearRing a #

Foldable LinearRing Source #

This instance of Foldable will run through the entire ring, closing the loop by also passing the initial element in again at the end.

Instance details

Defined in Data.LinearRing

Methods

fold :: Monoid m => LinearRing m -> m #

foldMap :: Monoid m => (a -> m) -> LinearRing a -> m #

foldr :: (a -> b -> b) -> b -> LinearRing a -> b #

foldr' :: (a -> b -> b) -> b -> LinearRing a -> b #

foldl :: (b -> a -> b) -> b -> LinearRing a -> b #

foldl' :: (b -> a -> b) -> b -> LinearRing a -> b #

foldr1 :: (a -> a -> a) -> LinearRing a -> a #

foldl1 :: (a -> a -> a) -> LinearRing a -> a #

toList :: LinearRing a -> [a] #

null :: LinearRing a -> Bool #

length :: LinearRing a -> Int #

elem :: Eq a => a -> LinearRing a -> Bool #

maximum :: Ord a => LinearRing a -> a #

minimum :: Ord a => LinearRing a -> a #

sum :: Num a => LinearRing a -> a #

product :: Num a => LinearRing a -> a #

Traversable LinearRing Source #

When traversing this Structure, the Applicative context of the last element will be appended to the end to close the loop

Instance details

Defined in Data.LinearRing

Methods

traverse :: Applicative f => (a -> f b) -> LinearRing a -> f (LinearRing b) #

sequenceA :: Applicative f => LinearRing (f a) -> f (LinearRing a) #

mapM :: Monad m => (a -> m b) -> LinearRing a -> m (LinearRing b) #

sequence :: Monad m => LinearRing (m a) -> m (LinearRing a) #

Eq a => Eq (LinearRing a) Source # 
Instance details

Defined in Data.LinearRing

Methods

(==) :: LinearRing a -> LinearRing a -> Bool #

(/=) :: LinearRing a -> LinearRing a -> Bool #

Show a => Show (LinearRing a) Source # 
Instance details

Defined in Data.LinearRing

Generic (LinearRing a) Source # 
Instance details

Defined in Data.LinearRing

Associated Types

type Rep (LinearRing a) :: * -> * #

Methods

from :: LinearRing a -> Rep (LinearRing a) x #

to :: Rep (LinearRing a) x -> LinearRing a #

ToJSON a => ToJSON (LinearRing a) Source # 
Instance details

Defined in Data.LinearRing

(Eq a, FromJSON a, Show a) => FromJSON (LinearRing a) Source # 
Instance details

Defined in Data.LinearRing

NFData a => NFData (LinearRing a) Source # 
Instance details

Defined in Data.LinearRing

Methods

rnf :: LinearRing a -> () #

type Rep (LinearRing a) Source # 
Instance details

Defined in Data.LinearRing

data ListToLinearRingError a Source #

When converting a List to a LinearRing there are some things that can go wrong

  • The list can be too short
  • The head may not be equal to the last element in the list (NB this is not currently checked due to performance concerns, and it also doesnt make much sense since its likely to contain doubles)

data SequenceToLinearRingError a Source #

When converting a Sequence to a LinearRing there are some things that can go wrong

  • The sequence can be too short
  • The head may not be equal to the last element in the list

Functions

toSeq :: LinearRing a -> Seq a Source #

create a sequence from a LinearRing. LinearRing 1 2 3 [4,1] --> Seq [1,2,3,4,1)]

combineToSeq :: (a -> a -> b) -> LinearRing a -> Seq b Source #

create a sequence from a LinearRing by combining values. LinearRing 1 2 3 4,1 --> Seq [(1,2),(2,3),(3,4),(4,1)]

fromSeq :: (Eq a, Show a, Validate v, Functor (v (NonEmpty (ListToLinearRingError a)))) => Seq a -> v (NonEmpty (SequenceToLinearRingError a)) (LinearRing a) Source #

creates a LinearRing out of a sequence of elements, if there are enough elements (needs at least 3) elements

fromSeq (x:y:z:ws@(_:_)) = _Success # LinearRing x y z (fromListDropLast ws) fromSeq xs = _Failure # return (ListTooShort (length xs))

fromLinearRing :: LinearRing a -> [a] Source #

This function converts it into a list and appends the given element to the end.

fromList :: (Eq a, Show a, Validate v, Functor (v (NonEmpty (ListToLinearRingError a)))) => [a] -> v (NonEmpty (ListToLinearRingError a)) (LinearRing a) Source #

creates a LinearRing out of a list of elements, if there arent enough elements (needs at least 4) elements

This version doesnt check equality of the head and tail in case you wish to use it for elements with no Eq instance defined.

Also its a list, finding the last element could be expensive with large lists. So just follow the spec and make sure the ring is closed.

Ideally the Spec would be modified to remove the redundant last element from the Polygons/LineRings. Its just going to waste bandwidth...

And be aware that the last element of the list will be dropped.

Unfortunately it doesn't check that the last element is the same as the first at the moment...

fromListWithEqCheck :: (Eq a, Show a, Validate v, Applicative (v (NonEmpty (ListToLinearRingError a)))) => [a] -> v (NonEmpty (ListToLinearRingError a)) (LinearRing a) Source #

The expensive version of fromList that checks whether the head and last elements are equal.

makeLinearRing Source #

Arguments

:: (Eq a, Show a) 
=> a

The first element

-> a

The second element

-> a

The third element

-> Seq a

The rest of the optional elements (WITHOUT the first element repeated at the end)

-> LinearRing a 

Creates a LinearRing makeLinearRing x y z xs creates a LinearRing homomorphic to the list [x, y, z] ++ xs the list xs should NOT contain the first element repeated, i.e the loop does not need to be closed, makeLinearRing will close it off.

Repeating the first element is just redundant.

ringHead :: LinearRing a -> a Source #

returns the element at the head of the ring

ringLength :: LinearRing a -> Int Source #

returns the number of elements in the list, including the replicated element at the end of the list.