{-# LANGUAGE CPP, Safe, TupleSections #-}
#ifdef GENERICS
{-# LANGUAGE TypeOperators, DefaultSignatures, FlexibleContexts, TypeApplications #-}
#endif
module Data.Unfoldable
(
Unfoldable(..)
, unfold_
, unfoldBF
, unfoldBF_
, unfoldr
, fromList
, leftMost
, rightMost
, allDepthFirst
, allToDepth
, allBreadthFirst
, randomDefault
, arbitraryDefault
)
where
import Control.Applicative
import Data.Unfolder
import Data.Functor.Compose
import Data.Functor.Constant
import Data.Functor.Identity
import Data.Functor.Product
import Data.Functor.Reverse
import Data.Functor.Sum
import Control.Monad.Trans.State
import qualified System.Random as R
import Test.QuickCheck (Arbitrary(..), Gen, sized, resize)
import Data.Maybe
import qualified Data.Sequence as S
import qualified Data.Tree as T
#ifdef GENERICS
import GHC.Generics
import Generics.OneLiner
#endif
class Unfoldable t where
unfold :: Unfolder f => f a -> f (t a)
#ifdef GENERICS
default unfold :: (ADT1 t, Constraints1 t Unfoldable, Unfolder f) => f a -> f (t a)
unfold = choose . getCompose . createA1 @Unfoldable (Compose . pure . unfold . asum' . getCompose) . Compose . pure
where
asum' [] = empty
asum' [a] = a
asum' (a:as) = a <|> asum' as
{-# INLINE unfold #-}
#endif
unfold_ :: (Unfoldable t, Unfolder f) => f (t ())
unfold_ = unfold (pure ())
unfoldBF :: (Unfoldable t, Unfolder f) => f a -> f (t a)
unfoldBF = ala bfs unfold
unfoldBF_ :: (Unfoldable t, Unfolder f) => f (t ())
unfoldBF_ = bfs unfold_
unfoldr :: Unfoldable t => (b -> Maybe (a, b)) -> b -> Maybe (t a)
unfoldr f z = terminate . flip runStateT z . unfoldBF . StateT $ maybeToList . f
where
terminate [] = Nothing
terminate ((t, b):ts) = if isNothing (f b) then Just t else terminate ts
fromList :: Unfoldable t => [a] -> Maybe (t a)
fromList = unfoldr uncons
where
uncons [] = Nothing
uncons (a:as) = Just (a, as)
leftMost :: Unfoldable t => Maybe (t ())
leftMost = unfold_
rightMost :: Unfoldable t => Maybe (t ())
rightMost = getDualA unfold_
allDepthFirst :: Unfoldable t => [t ()]
allDepthFirst = unfold_
allToDepth :: Unfoldable t => Int -> [t ()]
allToDepth d = limitDepth d unfold_
allBreadthFirst :: Unfoldable t => [t ()]
allBreadthFirst = unfoldBF_
randomDefault :: (R.Random a, R.RandomGen g, Unfoldable t) => g -> (t a, g)
randomDefault = runState . getRandom . unfold . Random . state $ R.random
arbitraryDefault :: (Arbitrary a, Unfoldable t) => Gen (t a)
arbitraryDefault = let Arb _ _ gen = unfold arbUnit in
fromMaybe (error "Failed to generate a value.") <$> gen
instance Unfoldable [] where
unfold fa = go where
go = choose
[ pure []
, (:) <$> fa <*> go ]
instance Unfoldable Maybe where
unfold fa = choose
[ pure Nothing
, Just <$> fa
]
instance (Bounded a, Enum a) => Unfoldable (Either a) where
unfold fa = choose
[ Left <$> boundedEnum
, Right <$> fa
]
instance (Bounded a, Enum a) => Unfoldable ((,) a) where
unfold fa = choose
[ (,) <$> boundedEnum <*> fa ]
instance Unfoldable Identity where
unfold fa = choose
[ Identity <$> fa ]
instance (Bounded a, Enum a) => Unfoldable (Constant a) where
unfold _ = choose
[ Constant <$> boundedEnum ]
instance (Unfoldable p, Unfoldable q) => Unfoldable (Product p q) where
unfold fa = choose
[ Pair <$> unfold fa <*> unfold fa ]
instance (Unfoldable p, Unfoldable q) => Unfoldable (Sum p q) where
unfold fa = choose
[ InL <$> unfold fa
, InR <$> unfold fa
]
instance (Unfoldable p, Unfoldable q) => Unfoldable (Compose p q) where
unfold fa = choose
[ Compose <$> unfold (unfold fa) ]
instance Unfoldable f => Unfoldable (Reverse f) where
unfold fa = choose
[ Reverse <$> getDualA (unfold (DualA fa)) ]
instance Unfoldable S.Seq where
unfold fa = go where
go = choose
[ pure empty
, (S.<|) <$> fa <*> go ]
instance Unfoldable T.Tree where
unfold fa = go where
go = choose [ T.Node <$> fa <*> unfold go ]