module Data.NonEmpty.Class where import qualified Data.Sequence as Seq import qualified Data.Set as Set import qualified Data.List.HT as ListHT import qualified Data.List as List import Data.Sequence (Seq, ) import Data.Set (Set, ) import Control.Monad (liftM2, ) import qualified Test.QuickCheck as QC import qualified Prelude as P import Prelude hiding (Show, showsPrec, zipWith, reverse, ) class Empty f where empty :: f a instance Empty [] where empty = [] instance Empty Maybe where empty = Nothing instance Empty Set where empty = Set.empty instance Empty Seq where empty = Seq.empty class Cons f where cons :: a -> f a -> f a instance Cons [] where cons = (:) instance Cons Seq where cons = (Seq.<|) class View f where viewL :: f a -> Maybe (a, f a) instance View [] where viewL = ListHT.viewL instance View Maybe where viewL = fmap (\a -> (a, Nothing)) instance View Set where viewL = Set.minView instance View Seq where viewL x = case Seq.viewl x of Seq.EmptyL -> Nothing y Seq.:< ys -> Just (y,ys) -- viewL x = do y Seq.:< ys <- Just $ Seq.viewl x; Just (y,ys) class Singleton f where singleton :: a -> f a instance Singleton [] where singleton x = [x] instance Singleton Maybe where singleton x = Just x instance Singleton Set where singleton = Set.singleton instance Singleton Seq where singleton = Seq.singleton class Append f where append :: f a -> f a -> f a instance Append [] where append = (++) instance Append Seq where append = (Seq.><) infixr 5 `cons`, `append` {- | It must hold: > fmap f xs > = zipWith (\x _ -> f x) xs xs > = zipWith (\_ x -> f x) xs xs -} class Functor f => Zip f where zipWith :: (a -> b -> c) -> f a -> f b -> f c instance Zip [] where zipWith = List.zipWith instance Zip Maybe where zipWith = liftM2 instance Zip Seq where zipWith = Seq.zipWith zip :: (Zip f) => f a -> f b -> f (a,b) zip = zipWith (,) class Repeat f where {- | Create a container with as many copies as possible of a given value. That is, for a container with fixed size @n@, the call @repeat x@ will generate a container with @n@ copies of @x@. -} repeat :: a -> f a instance Repeat [] where repeat = List.repeat class Sort f where sortBy :: (a -> a -> Ordering) -> f a -> f a instance Sort [] where sortBy = List.sortBy instance Sort Maybe where sortBy _f = id instance Sort Seq where sortBy = Seq.sortBy sort :: (Ord a, Sort f) => f a -> f a sort = sortBy compare class Reverse f where reverse :: f a -> f a instance Reverse [] where reverse = List.reverse instance Reverse Maybe where reverse = id instance Reverse Seq where reverse = Seq.reverse class Show f where showsPrec :: P.Show a => Int -> f a -> ShowS instance Show [] where showsPrec p xs = if null xs then showString "[]" else showParen (p>5) $ foldr (.) (showString "[]") $ map (\x -> P.showsPrec 6 x . showString ":") xs class Arbitrary f where arbitrary :: QC.Arbitrary a => QC.Gen (f a) shrink :: QC.Arbitrary a => f a -> [f a] instance Arbitrary [] where arbitrary = QC.arbitrary shrink = QC.shrink