{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE Trustworthy #-}
{-# LANGUAGE ViewPatterns, ScopedTypeVariables #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE MultiParamTypeClasses, UndecidableInstances #-}
module Data.Extensible.Product (
(:&)
, (:*)
, nil
, (<:)
, (<!)
, (=<:)
, hlength
, type (++)
, happend
, hmap
, hmapWithIndex
, hzipWith
, hzipWith3
, hfoldMap
, hfoldMapWithIndex
, hfoldrWithIndex
, hfoldlWithIndex
, htraverse
, htraverseWithIndex
, hsequence
, hmapWithIndexFor
, hfoldMapFor
, hfoldMapWithIndexFor
, hfoldrWithIndexFor
, hfoldlWithIndexFor
, hfoldMapWith
, hfoldMapWithIndexWith
, hfoldrWithIndexWith
, hfoldlWithIndexWith
, hmapWithIndexWith
, hforce
, haccumMap
, haccum
, hpartition
, hlookup
, hindex
, Generate(..)
, hgenerate
, htabulate
, hrepeat
, hcollect
, hdistribute
, fromHList
, toHList
, Forall(..)
, hgenerateFor
, htabulateFor
, hrepeatFor
, hgenerateWith
, htabulateWith
, hrepeatWith) where
import Data.Extensible.Internal.Rig (review)
import Data.Extensible.Struct
import Data.Extensible.Sum
import Data.Extensible.Class
import Data.Extensible.Wrapper
import Data.Proxy
import qualified Type.Membership.HList as HList
(<:) :: h x -> xs :& h -> (x ': xs) :& h
(<:) x = fromHList . HList.HCons x . toHList
{-# INLINE (<:) #-}
infixr 0 <:
(=<:) :: Wrapper h => Repr h x -> xs :& h -> (x ': xs) :& h
(=<:) = (<:) . review _Wrapper
{-# INLINE (=<:) #-}
infixr 0 =<:
(<!) :: h x -> xs :& h -> (x ': xs) :& h
(<!) x = fromHList . (HList.HCons $! x) . toHList
{-# INLINE (<!) #-}
infixr 0 <!
nil :: '[] :& h
nil = hfrozen $ new $ error "Impossible"
{-# NOINLINE nil #-}
{-# RULES "toHList/nil" toHList nil = HList.HNil #-}
fromHList :: HList.HList h xs -> xs :& h
fromHList xs = hfrozen (newFromHList xs)
{-# INLINE fromHList #-}
hindex :: xs :& h -> Membership xs x -> h x
hindex = flip hlookup
{-# INLINE hindex #-}
hmapWithIndex :: (forall x. Membership xs x -> g x -> h x) -> xs :& g -> xs :& h
hmapWithIndex t p = hfrozen (newFrom p t)
{-# INLINE hmapWithIndex #-}
hmapWithIndexFor :: Forall c xs
=> proxy c
-> (forall x. c x => Membership xs x -> g x -> h x)
-> xs :& g -> xs :& h
hmapWithIndexFor c t p = hfrozen $ newFor c $ \i -> t i $ hlookup i p
{-# INLINE hmapWithIndexFor #-}
hmapWithIndexWith :: forall c xs g h. Forall c xs
=> (forall x. c x => Membership xs x -> g x -> h x)
-> xs :& g -> xs :& h
hmapWithIndexWith = hmapWithIndexFor (Proxy @ c)
hmap :: (forall x. g x -> h x) -> xs :& g -> xs :& h
hmap f = hmapWithIndex (const f)
{-# INLINE hmap #-}
hzipWith :: (forall x. f x -> g x -> h x) -> xs :& f -> xs :& g -> xs :& h
hzipWith t xs = hmapWithIndex (\i -> t (hlookup i xs))
{-# INLINE hzipWith #-}
hzipWith3 :: (forall x. f x -> g x -> h x -> i x) -> xs :& f -> xs :& g -> xs :& h -> xs :& i
hzipWith3 t xs ys = hmapWithIndex (\i -> t (hlookup i xs) (hlookup i ys))
{-# INLINE hzipWith3 #-}
hfoldMap :: Monoid a => (forall x. h x -> a) -> xs :& h -> a
hfoldMap f = hfoldMapWithIndex (const f)
{-# INLINE hfoldMap #-}
hfoldMapWithIndex :: Monoid a
=> (forall x. Membership xs x -> g x -> a) -> xs :& g -> a
hfoldMapWithIndex f = hfoldrWithIndex (\i -> mappend . f i) mempty
{-# INLINE hfoldMapWithIndex #-}
hfoldlWithIndex :: (forall x. Membership xs x -> r -> h x -> r) -> r -> xs :& h -> r
hfoldlWithIndex f r xs = hfoldrWithIndex (\i x c a -> c $! f i a x) id xs r
{-# INLINE hfoldlWithIndex #-}
hfoldrWithIndexFor :: forall c xs h r proxy. (Forall c xs) => proxy c
-> (forall x. c x => Membership xs x -> h x -> r -> r) -> r -> xs :& h -> r
hfoldrWithIndexFor p f r xs = henumerateFor p (Proxy :: Proxy xs) (\i -> f i (hlookup i xs)) r
{-# INLINE hfoldrWithIndexFor #-}
hfoldrWithIndexWith :: forall c xs h r. (Forall c xs)
=> (forall x. c x => Membership xs x -> h x -> r -> r) -> r -> xs :& h -> r
hfoldrWithIndexWith f r xs = henumerateFor (Proxy @ c) (Proxy @ xs) (\i -> f i (hlookup i xs)) r
{-# INLINE hfoldrWithIndexWith #-}
hfoldlWithIndexFor :: (Forall c xs) => proxy c
-> (forall x. c x => Membership xs x -> r -> h x -> r) -> r -> xs :& h -> r
hfoldlWithIndexFor p f r xs = hfoldrWithIndexFor p (\i x c a -> c $! f i a x) id xs r
{-# INLINE hfoldlWithIndexFor #-}
hfoldlWithIndexWith :: forall c xs h r. (Forall c xs)
=> (forall x. c x => Membership xs x -> r -> h x -> r) -> r -> xs :& h -> r
hfoldlWithIndexWith f r xs = hfoldrWithIndexWith @c (\i x c a -> c $! f i a x) id xs r
{-# INLINE hfoldlWithIndexWith #-}
hfoldMapWithIndexFor :: (Forall c xs, Monoid a) => proxy c
-> (forall x. c x => Membership xs x -> h x -> a) -> xs :& h -> a
hfoldMapWithIndexFor p f = hfoldrWithIndexFor p (\i -> mappend . f i) mempty
{-# INLINE hfoldMapWithIndexFor #-}
hfoldMapWithIndexWith :: forall c xs h a. (Forall c xs, Monoid a)
=> (forall x. c x => Membership xs x -> h x -> a) -> xs :& h -> a
hfoldMapWithIndexWith f = hfoldrWithIndexWith @c (\i -> mappend . f i) mempty
{-# INLINE hfoldMapWithIndexWith #-}
hfoldMapFor :: (Forall c xs, Monoid a) => proxy c
-> (forall x. c x => h x -> a) -> xs :& h -> a
hfoldMapFor p f = hfoldMapWithIndexFor p (const f)
{-# INLINE hfoldMapFor #-}
hfoldMapWith :: forall c xs h a. (Forall c xs, Monoid a)
=> (forall x. c x => h x -> a) -> xs :& h -> a
hfoldMapWith f = hfoldMapWithIndexFor (Proxy @ c) (const f)
{-# INLINE hfoldMapWith #-}
htraverse :: Applicative f => (forall x. g x -> f (h x)) -> xs :& g -> f (xs :& h)
htraverse f = fmap fromHList . HList.htraverse f . toHList
{-# INLINE htraverse #-}
hsequence :: Applicative f => xs :& Comp f h -> f (xs :& h)
hsequence = htraverse getComp
{-# INLINE hsequence #-}
hcollect :: (Functor f, Generate xs) => (a -> xs :& h) -> f a -> xs :& Comp f h
hcollect f m = htabulate $ \i -> Comp $ fmap (hlookup i . f) m
{-# INLINABLE hcollect #-}
hdistribute :: (Functor f, Generate xs) => f (xs :& h) -> xs :& Comp f h
hdistribute = hcollect id
{-# INLINE hdistribute #-}
htraverseWithIndex :: Applicative f
=> (forall x. Membership xs x -> g x -> f (h x)) -> xs :& g -> f (xs :& h)
htraverseWithIndex f = fmap fromHList . HList.htraverseWithIndex f . toHList
{-# INLINE htraverseWithIndex #-}
hrepeat :: Generate xs => (forall x. h x) -> xs :& h
hrepeat x = hfrozen $ newRepeat x
{-# INLINE hrepeat #-}
htabulate :: Generate xs => (forall x. Membership xs x -> h x) -> xs :& h
htabulate f = hfrozen $ new f
{-# INLINE htabulate #-}
hgenerate :: (Generate xs, Applicative f)
=> (forall x. Membership xs x -> f (h x)) -> f (xs :& h)
hgenerate f = fmap fromHList $ hgenerateList f
{-# INLINE hgenerate #-}
htabulateFor :: Forall c xs => proxy c -> (forall x. c x => Membership xs x -> h x) -> xs :& h
htabulateFor p f = hfrozen $ newFor p f
{-# INLINE htabulateFor #-}
htabulateWith :: forall c xs h. Forall c xs => (forall x. c x => Membership xs x -> h x) -> xs :& h
htabulateWith f = hfrozen $ newFor (Proxy @ c) f
{-# INLINE htabulateWith #-}
hrepeatFor :: Forall c xs => proxy c -> (forall x. c x => h x) -> xs :& h
hrepeatFor p f = htabulateFor p (const f)
{-# INLINE hrepeatFor #-}
hrepeatWith :: forall c xs h. Forall c xs => (forall x. c x => h x) -> xs :& h
hrepeatWith f = htabulateFor (Proxy @ c) (const f)
{-# INLINE hrepeatWith #-}
hgenerateFor :: (Forall c xs, Applicative f)
=> proxy c -> (forall x. c x => Membership xs x -> f (h x)) -> f (xs :& h)
hgenerateFor p f = fmap fromHList $ hgenerateListFor p f
{-# INLINE hgenerateFor #-}
hgenerateWith :: forall c xs f h. (Forall c xs, Applicative f)
=> (forall x. c x => Membership xs x -> f (h x)) -> f (xs :& h)
hgenerateWith f = fmap fromHList $ hgenerateListFor (Proxy @ c) f
{-# INLINE hgenerateWith #-}
haccumMap :: Foldable f
=> (a -> xs :/ g)
-> (forall x. Membership xs x -> g x -> h x -> h x)
-> xs :& h -> f a -> xs :& h
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
{-# INLINE haccumMap #-}
haccum :: Foldable f
=> (forall x. Membership xs x -> g x -> h x -> h x)
-> xs :& h -> f (xs :/ g) -> xs :& h
haccum = haccumMap id
{-# INLINE haccum #-}
hpartition :: (Foldable f, Generate xs) => (a -> xs :/ h) -> f a -> xs :& Comp [] h
hpartition f = haccumMap f (\_ x (Comp xs) -> Comp (x:xs)) $ hrepeat $ Comp []
{-# INLINE hpartition #-}
hforce :: xs :& h -> xs :& h
hforce p = hfoldrWithIndex (const seq) p p
{-# INLINE hforce #-}