module Data.Function.HT.Private where
import Data.List (genericReplicate, unfoldr)
import Data.Maybe.HT (toMaybe)
import Data.Tuple.HT (swap)
{-# INLINE nest #-}
nest, nest1, nest2 :: Int -> (a -> a) -> a -> a
nest 0 _ x = x
nest n f x = f (nest (n-1) f x)
nest1 n f = foldr (.) id (replicate n f)
nest2 n f x = iterate f x !! n
{-# INLINE powerAssociative #-}
powerAssociative, powerAssociativeList, powerAssociativeNaive ::
(a -> a -> a) -> a -> a -> Integer -> a
powerAssociative op =
let go acc _ 0 = acc
go acc a n = go (if even n then acc else op acc a) (op a a) (div n 2)
in go
powerAssociativeList op a0 a n =
foldl (\acc (bit,pow) -> if bit==0 then acc else op acc pow) a0 $
zip
(unfoldr (\k -> toMaybe (k>0) $ swap $ divMod k 2) n)
(iterate (\pow -> op pow pow) a)
powerAssociativeNaive op a0 a n =
foldr op a0 (genericReplicate n a)
infixl 0 $%
($%) :: a -> (a -> b) -> b
($%) = flip ($)