module Resource.Collection ( enumerate , size , toVector , toVectorStorable , Generic1 , Generically1(..) ) where import RIO import Data.List qualified as List import Data.Traversable (mapAccumL) import GHC.Generics (Generic1, Generically1(..)) import RIO.Vector qualified as Vector import RIO.Vector.Storable qualified as VectorStorable {-# INLINE size #-} size :: (Foldable t, Num size) => t a -> size size = List.genericLength . toList enumerate :: (Traversable t, Num ix) => t a -> t (ix, a) enumerate = snd . mapAccumL f 0 where f a b = (a + 1, (a, b)) {-# INLINE toVector #-} toVector :: Foldable collection => collection a -> Vector a toVector = Vector.fromList . toList {-# INLINE toVectorStorable #-} toVectorStorable :: (Foldable collection, Storable a) => collection a -> VectorStorable.Vector a toVectorStorable = VectorStorable.fromList . toList data Example a = Example { one :: a , two :: a -- , nay :: Bool , huh :: [Bool] } deriving stock (Eq, Ord, Show, Functor, Foldable, Traversable, Generic1) deriving Applicative via Generically1 Example _example :: Example (Char, Int) _example = (,) <$> pure '!' <*> pure 2