{-# LANGUAGE NoImplicitPrelude #-}
module Data.LinearRing (
LinearRing
, ListToLinearRingError(..)
, fromLinearRing
, fromList
, fromListWithEqCheck
, makeLinearRing
, ringHead
, ringLength
) where
import Prelude hiding (foldr)
import Control.Applicative (Applicative (..))
import Control.Lens (( # ), (^?))
import Control.Monad (mzero)
import Data.Aeson (FromJSON (..), ToJSON (..), Value)
import Data.Aeson.Types (Parser, typeMismatch)
import Data.Foldable (Foldable (..))
import Data.Functor ((<$>))
import Data.List (intercalate)
import Data.List.NonEmpty as NL (NonEmpty, toList)
import Data.Traversable (Traversable (..))
import Data.Validation (Validate (..), Validation, _Failure,
_Success)
data LinearRing a = LinearRing a a a [a] deriving (Eq)
data ListToLinearRingError a =
ListTooShort Int
| HeadNotEqualToLast a a
deriving (Eq)
ringHead :: LinearRing a -> a
ringHead (LinearRing x _ _ _) = x
ringLength :: LinearRing a -> Int
ringLength (LinearRing _ _ _ xs) = 4 + length xs
fromLinearRing :: LinearRing a -> [a]
fromLinearRing (LinearRing x y z ws) = x : y : z : foldr (:) [x] ws
fromList
:: (Validate v, Functor (v (NonEmpty (ListToLinearRingError a))))
=> [a]
-> v (NonEmpty (ListToLinearRingError a)) (LinearRing a)
fromList (x:y:z:ws@(_:_)) = _Success # LinearRing x y z (foldrDropLast (:) [] ws)
fromList xs = _Failure # return (ListTooShort (length xs))
fromListWithEqCheck
:: (Eq a, Validate v, Applicative (v (NonEmpty (ListToLinearRingError a))))
=> [a]
-> v (NonEmpty (ListToLinearRingError a)) (LinearRing a)
fromListWithEqCheck xs = checkHeadAndLastEq xs *> fromList xs
makeLinearRing
:: a
-> a
-> a
-> [a]
-> LinearRing a
makeLinearRing = LinearRing
instance (Show a) => Show (ListToLinearRingError a) where
show (ListTooShort n) = "List too short: (length = " ++ show n ++ ")"
show (HeadNotEqualToLast h l) = "head (" ++ show h ++ ") /= last(" ++ show l ++ ")"
instance (Show a) => Show (LinearRing a) where
show = show . fromLinearRing
instance Functor LinearRing where
fmap f (LinearRing x y z ws) = LinearRing (f x) (f y) (f z) (fmap f ws)
instance Foldable LinearRing where
foldr f u (LinearRing x y z ws) = f x (f y (f z (foldr f (f x u) ws)))
instance Traversable LinearRing where
sequenceA (LinearRing fx fy fz fws) = (LinearRing <$> fx <*> fy <*> fz <*> sequenceA fws) <* fx
instance (ToJSON a) => ToJSON (LinearRing a) where
toJSON = toJSON . fromLinearRing
instance (FromJSON a, Show a) => FromJSON (LinearRing a) where
parseJSON v = do
xs <- parseJSON v
let vxs = fromListAcc xs
maybe (parseError v (vxs ^? _Failure)) return (vxs ^? _Success)
fromListAcc :: [a] -> Validation (NonEmpty (ListToLinearRingError a)) (LinearRing a)
fromListAcc = fromList
showErrors :: (Show a) => NonEmpty (ListToLinearRingError a) -> String
showErrors = intercalate ", " . NL.toList . fmap show
parseError :: (Show a) => Value -> Maybe (NonEmpty (ListToLinearRingError a)) -> Parser b
parseError v = maybe mzero (\e -> typeMismatch (showErrors e) v)
checkHeadAndLastEq
:: (Eq a, Validate v, Functor (v (NonEmpty (ListToLinearRingError a))))
=> [a]
-> v (NonEmpty (ListToLinearRingError a)) ()
checkHeadAndLastEq = maybe (_Failure # return (ListTooShort 0)) (\(h, l) -> if h == l then _Success # () else _Failure # return (HeadNotEqualToLast h l)) . mhl
where
mhl ::[a] -> Maybe (a, a)
mhl xs = (,) <$> safeHead xs <*> safeLast xs
safeHead :: [a] -> Maybe a
safeHead [] = Nothing
safeHead (x:_) = Just x
safeLast :: [a] -> Maybe a
safeLast [] = Nothing
safeLast [x] = Just x
safeLast (_:xs) = safeLast xs
foldrDropLast :: (a -> b -> b) -> b -> [a] -> b
foldrDropLast _ x [] = x
foldrDropLast _ x [_] = x
foldrDropLast f x (y:ys) = f y (foldrDropLast f x ys)