module Data.Extensible.Product (
  
  (:*)
  , nil
  , (<:)
  , (<!)
  , hlength
  , type (++)
  , happend
  , hmap
  , hmapWithIndex
  , hzipWith
  , hzipWith3
  , hfoldMap
  , hfoldMapWithIndex
  , hfoldrWithIndex
  , hfoldlWithIndex
  , htraverse
  , htraverseWithIndex
  , hsequence
  
  , hfoldMapFor
  , hfoldMapWithIndexFor
  , hfoldrWithIndexFor
  , hfoldlWithIndexFor
  
  , hforce
  
  , haccumMap
  , haccum
  , hpartition
  
  , hlookup
  , hindex
  
  , Generate(..)
  , hgenerate
  , htabulate
  , hrepeat
  , hcollect
  , hdistribute
  , fromHList
  , toHList
  , Forall(..)
  , hgenerateFor
  , htabulateFor
  , hrepeatFor) where
import Data.Extensible.Internal
import Data.Extensible.Struct
import Data.Extensible.Sum
#if !MIN_VERSION_base(4,8,0)
import Control.Applicative
#endif
import Data.Extensible.Class
import qualified Data.Extensible.HList as HList
import Data.Extensible.Wrapper
(<:) :: h x -> h :* xs -> h :* (x ': xs)
(<:) x = fromHList . HList.HCons x . toHList
infixr 0 <:
(<!) :: h x -> h :* xs -> h :* (x ': xs)
(<!) x = fromHList . (HList.HCons $! x) . toHList
infixr 0 <!
nil :: h :* '[]
nil = hfrozen $ new $ error "Impossible"
fromHList :: HList.HList h xs -> h :* xs
fromHList xs = hfrozen (newFromHList xs)
hindex :: h :* xs -> Membership xs x ->  h x
hindex = flip hlookup
hmapWithIndex :: (forall x. Membership xs x -> g x -> h x) -> g :* xs -> h :* xs
hmapWithIndex t p = hfrozen (newFrom p t)
hmap :: (forall x. g x -> h x) -> g :* xs -> h :* xs
hmap f = hmapWithIndex (const f)
hzipWith :: (forall x. f x -> g x -> h x) -> f :* xs -> g :* xs -> h :* xs
hzipWith t xs = hmapWithIndex (\i -> t (hlookup i xs))
hzipWith3 :: (forall x. f x -> g x -> h x -> i x) -> f :* xs -> g :* xs -> h :* xs -> i :* xs
hzipWith3 t xs ys = hmapWithIndex (\i -> t (hlookup i xs) (hlookup i ys))
hfoldMap :: Monoid a => (forall x. h x -> a) -> h :* xs -> a
hfoldMap f = hfoldMapWithIndex (const f)
hfoldMapWithIndex :: Monoid a
  => (forall x. Membership xs x -> g x -> a) -> g :* xs -> a
hfoldMapWithIndex f = hfoldrWithIndex (\i -> mappend . f i) mempty
hfoldlWithIndex :: (forall x. Membership xs x -> r -> h x -> r) -> r -> h :* xs -> r
hfoldlWithIndex f r xs = hfoldrWithIndex (\i x c a -> c $! f i a x) id xs r
hfoldrWithIndexFor :: (Forall c xs) => proxy c
  -> (forall x. c x => Membership xs x -> h x -> r -> r) -> r -> h :* xs -> r
hfoldrWithIndexFor p f r xs = henumerateFor p xs (\i -> f i (hlookup i xs)) r
hfoldlWithIndexFor :: (Forall c xs) => proxy c
  -> (forall x. c x => Membership xs x -> r -> h x -> r) -> r -> h :* xs -> r
hfoldlWithIndexFor p f r xs = hfoldrWithIndexFor p (\i x c a -> c $! f i a x) id xs r
hfoldMapWithIndexFor :: (Forall c xs, Monoid a) => proxy c
  -> (forall x. c x => Membership xs x -> h x -> a) -> h :* xs -> a
hfoldMapWithIndexFor p f = hfoldrWithIndexFor p (\i -> mappend . f i) mempty
hfoldMapFor :: (Forall c xs, Monoid a) => proxy c
  -> (forall x. c x => h x -> a) -> h :* xs -> a
hfoldMapFor p f = hfoldMapWithIndexFor p (const f)
htraverse :: Applicative f => (forall x. g x -> f (h x)) -> g :* xs -> f (h :* xs)
htraverse f = fmap fromHList . HList.htraverse f . toHList
hsequence :: Applicative f => Comp f h :* xs -> f (h :* xs)
hsequence = htraverse getComp
hcollect :: (Functor f, Generate xs) => (a -> h :* xs) -> f a -> Comp f h :* xs
hcollect f m = htabulate $ \i -> Comp $ fmap (hlookup i . f) m
hdistribute :: (Functor f, Generate xs) => f (h :* xs) -> Comp f h :* xs
hdistribute = hcollect id
htraverseWithIndex :: Applicative f
  => (forall x. Membership xs x -> g x -> f (h x)) -> g :* xs -> f (h :* xs)
htraverseWithIndex f = fmap fromHList . HList.htraverseWithIndex f . toHList
hrepeat :: Generate xs => (forall x. h x) -> h :* xs
hrepeat x = hfrozen $ newRepeat x
htabulate :: Generate xs => (forall x. Membership xs x -> h x) -> h :* xs
htabulate f = hfrozen $ new f
hgenerate :: (Generate xs, Applicative f)
  => (forall x. Membership xs x -> f (h x)) -> f (h :* xs)
hgenerate f = fmap fromHList $ hgenerateList f
htabulateFor :: Forall c xs => proxy c -> (forall x. c x => Membership xs x -> h x) -> h :* xs
htabulateFor p f = hfrozen $ newFor p f
hrepeatFor :: Forall c xs => proxy c -> (forall x. c x => h x) -> h :* xs
hrepeatFor p f = htabulateFor p (const f)
hgenerateFor :: (Forall c xs, Applicative f)
  => proxy c -> (forall x. c x => Membership xs x -> f (h x)) -> f (h :* xs)
hgenerateFor p f = fmap fromHList $ hgenerateListFor p f
haccumMap :: Foldable f
  => (a -> g :| xs)
  -> (forall x. Membership xs x -> g x -> h x -> h x)
  -> h :* xs -> f a -> h :* xs
haccumMap f g p0 xs = hmodify
  (\s -> mapM_ (\x -> case f x of EmbedAt i v -> get s i >>= set s i . g i v) xs)
  p0
haccum :: Foldable f
  => (forall x. Membership xs x -> g x -> h x -> h x)
  -> h :* xs -> f (g :| xs) -> h :* xs
haccum = haccumMap id
hpartition :: (Foldable f, Generate xs) => (a -> h :| xs) -> f a -> Comp [] h :* xs
hpartition f = haccumMap f (\_ x (Comp xs) -> Comp (x:xs)) $ hrepeat $ Comp []
hforce :: h :* xs -> h :* xs
hforce p = hfoldrWithIndex (const seq) p p