{-# LANGUAGE Safe #-}
module Data.Biunfoldable
  (
  
    Biunfoldable(..)
  , biunfold_
  , biunfoldBF
  , biunfoldBF_
  
  , biunfoldr
  , fromLists
  , randomDefault
  , arbitraryDefault
  )
  where
import Control.Applicative
import Data.Unfolder
import Data.Functor.Constant
import Control.Monad.Trans.State
import qualified System.Random as R
import Test.QuickCheck (Arbitrary(..), Gen, sized, resize)
import Data.Maybe
class Biunfoldable t where
  
  biunfold :: Unfolder f => f a -> f b -> f (t a b)
biunfold_ :: (Biunfoldable t, Unfolder f) => f (t () ())
biunfold_ = biunfold (pure ()) (pure ())
biunfoldBF :: (Biunfoldable t, Unfolder f) => f a -> f b -> f (t a b)
biunfoldBF = ala2 bfs biunfold
biunfoldBF_ :: (Biunfoldable t, Unfolder f) => f (t () ())
biunfoldBF_ = bfs biunfold_
biunfoldr :: Biunfoldable t => (c -> Maybe (a, c)) -> (c -> Maybe (b, c)) -> c -> Maybe (t a b)
biunfoldr fa fb z = terminate . flip runStateT z $ biunfoldBF (StateT $ maybeToList . fa) (StateT $ maybeToList . fb)
  where
    terminate [] = Nothing
    terminate ((t, c):ts) = if isNothing (fa c) && isNothing (fb c) then Just t else terminate ts
fromLists :: Biunfoldable t => [a] -> [b] -> Maybe (t a b)
fromLists = curry $ biunfoldr unconsA unconsB
  where
    unconsA ([], _) = Nothing
    unconsA (a:as, bs) = Just (a, (as, bs))
    unconsB (_, []) = Nothing
    unconsB (as, b:bs) = Just (b, (as, bs))
randomDefault :: (R.Random a, R.Random b, R.RandomGen g, Biunfoldable t) => g -> (t a b, g)
randomDefault = runState . getRandom $ biunfold (Random . state $ R.random) (Random . state $ R.random)
arbitraryDefault :: (Arbitrary a, Arbitrary b, Biunfoldable t) => Gen (t a b)
arbitraryDefault = let Arb _ _ gen = biunfold arbUnit arbUnit in
  fromMaybe (error "Failed to generate a value.") <$> gen
instance Biunfoldable Either where
  biunfold fa fb = choose
    [ Left <$> fa
    , Right <$> fb
    ]
instance Biunfoldable (,) where
  biunfold fa fb = choose
    [ (,) <$> fa <*> fb ]
instance Biunfoldable Constant where
  biunfold fa _ = choose
    [ Constant <$> fa ]