{-# LANGUAGE NoImplicitPrelude #-}
module Data.LineString (
LineString
, ListToLineStringError(..)
, fromLineString
, fromList
, makeLineString
, lineStringHead
, lineStringLast
, lineStringLength
) 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.Maybe (fromMaybe)
import Data.Traversable (Traversable (..))
import Data.Validation (Validate (..), Validation, _Failure,
_Success)
data LineString a = LineString a a [a] deriving (Eq)
data ListToLineStringError =
ListEmpty
| SingletonList
deriving (Eq)
lineStringHead :: LineString a -> a
lineStringHead (LineString x _ _) = x
lineStringLast :: LineString a -> a
lineStringLast (LineString _ x xs) = fromMaybe x (safeLast xs)
lineStringLength :: LineString a -> Int
lineStringLength (LineString _ _ xs) = 2 + length xs
fromLineString :: LineString a -> [a]
fromLineString (LineString x y zs) = x : y : zs
fromList :: (Validate v) => [a] -> v ListToLineStringError (LineString a)
fromList [] = _Failure # ListEmpty
fromList [_] = _Failure # SingletonList
fromList (x:y:zs) = _Success # LineString x y zs
makeLineString
:: a
-> a
-> [a]
-> LineString a
makeLineString = LineString
instance Show ListToLineStringError where
show ListEmpty = "List Empty"
show SingletonList = "Singleton List"
instance (Show a) => Show (LineString a) where
show = show . fromLineString
instance Functor LineString where
fmap f (LineString x y zs) = LineString (f x) (f y) (fmap f zs)
instance Foldable LineString where
foldr f u (LineString x y zs) = f x (f y (foldr f u zs))
instance Traversable LineString where
sequenceA (LineString fx fy fzs) = LineString <$> fx <*> fy <*> sequenceA fzs
instance (ToJSON a) => ToJSON (LineString a) where
toJSON = toJSON . fromLineString
instance (FromJSON a, Show a) => FromJSON (LineString a) where
parseJSON v = do
xs <- parseJSON v
let vxs = fromListValidated xs
maybe (parseError v (vxs ^? _Failure)) return (vxs ^? _Success)
fromListValidated :: [a] -> Validation ListToLineStringError (LineString a)
fromListValidated = fromList
parseError :: Value -> Maybe ListToLineStringError -> Parser b
parseError v = maybe mzero (\e -> typeMismatch (show e) v)
safeLast :: [a] -> Maybe a
safeLast [] = Nothing
safeLast [x] = Just x
safeLast (_:xs) = safeLast xs