{-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE ScopedTypeVariables #-} module Main where import Control.Applicative import Data.List.NonEmptyZipper import Data.Monoid () import Data.Semigroup import Prelude hiding (head, init, last, reverse, tail) import Test.QuickCheck import Test.QuickCheck.Checkers import Test.QuickCheck.Classes instance Arbitrary a => Arbitrary (NonEmptyZipper a) where arbitrary = liftA3 NonEmptyZipper arbitrary arbitrary arbitrary instance Eq a => EqProp (NonEmptyZipper a) where (=-=) = eq yo :: TestBatch -> IO () yo = checkBatch $ stdArgs { maxSuccess = 100, maxSize = 30 } instance {-# OVERLAPS #-} Monoid (Maybe (NonEmptyZipper a)) where mempty = Nothing mappend (Just x) (Just y) = Just $ x <> y mappend Nothing x = x mappend x Nothing = x main :: IO () main = do yo $ functor (NonEmptyZipper [] (0::Int, "", False) []) yo $ applicative (NonEmptyZipper [] (0::Int, "", False) []) yo $ monoid (Just $ NonEmptyZipper [] (0::Int, "", 0::Int) []) quickCheck $ \(x :: NonEmptyZipper Int) -> nextMod (previousMod x) == x && x == previousMod (nextMod x) quickCheck $ \(x :: NonEmptyZipper Int) -> reverse (reverse x) == x quickCheck $ \(x :: NonEmptyZipper Int) -> head (reverse x) == last x && head x == last (reverse x) quickCheck $ \(x :: NonEmptyZipper Int) -> fmap reverse (tail (reverse x)) == init x && tail x == fmap reverse (init (reverse x))