-- |This module provides support for adaptive tuples. -- An `AdaptiveTuple` is a tuple type with the size chosen at run-time and -- minimal overhead. All elements must be of the same type. Calculations -- are generated by combining adaptive tuples, which are then given an -- initial input with the `reifyTuple` function or its strict variant. -- -- Example: suppose you have a list of numbers that is either a single list -- or multiple interleaved lists. You wish to determine the maximum value -- of the single list or maximums of all interleaved lists. -- -- > -- |The second argument is a dummy argument to fix the type of c s () -- > -- so this function can be used directly with reifyTuple -- > deinterleave :: AdaptiveTuple c s => [Int] -> c s () -> [c s Int] -- > deinterleave [] _ = [] -- > deinterleave xs n = let (h, rest) = splitAt (tupLength n) xs -- > in toATuple h : deinterleave n rest -- > -- > maxVals :: AdaptiveTuple c s => [c s Int] -> c s Int -- > maxVals = foldl' (\a b -> max <$> a <*> b) (pure 0) -- > -- > runner :: Int -> [Int] -> [Int] -- > runner n xs = reifyStrictTuple n (repeat ()) -- > (fromATuple . maxVals . deinterleave xs) -- -- using AdaptiveTuple is similar to the `ZipList` applicative instance, except -- without the overhead. {-# LANGUAGE MultiParamTypeClasses ,Rank2Types #-} {-# OPTIONS_GHC -fno-warn-name-shadowing #-} module Data.AdaptiveTuple ( -- * Types -- ** Classes AdaptiveTuple (..) -- ** Exceptions ,AdaptiveTupleException (..) -- * Functions ,reifyTuple ,reifyStrictTuple ,invert ,mapIndexed ) where import Data.AdaptiveTuple.AdaptiveTuple import qualified Data.AdaptiveTuple.Reps.Lazy as L import qualified Data.AdaptiveTuple.Reps.Strict as S import Data.TypeLevel.Num as T import Control.Applicative -- -------------------------------------------------- -- |Lazily convert a list of AdaptiveTuples into an AdaptiveTuple of lists. invert :: (AdaptiveTuple c s) => [c s a] -> c s [a] invert [] = pure [] invert (x:xs) = (:) <$> x <*> invert xs -- |Map a 0-indexed function over an AdaptiveTuple mapIndexed :: (AdaptiveTuple c s) => (Int -> a -> b) -> c s a -> c s b mapIndexed f a = f <$> toATuple [0..] <*> a --default reification functions reifyTuple :: forall el r.Int -> [el] -> (forall c s.(AdaptiveTuple c s, T.Nat s) => c s el -> r) -> r reifyTuple = L.reifyTuple20 reifyStrictTuple :: forall el r.Int -> [el] -> (forall c s.(AdaptiveTuple c s, T.Nat s) => c s el -> r) -> r reifyStrictTuple = S.reifyTuple20