module RandomCycle.List.Partition where
import Control.Monad (guard)
import Data.Bits
import GHC.Natural (Natural)
import System.Random.Stateful
spanBits :: (Bool -> Bool) -> Natural -> [a] -> ([a], (Natural, [a]))
spanBits :: (Bool -> Bool) -> Natural -> [a] -> ([a], (Natural, [a]))
spanBits Bool -> Bool
_ Natural
bs xs :: [a]
xs@[] = ([a]
xs, (Natural
bs, [a]
xs))
spanBits Bool -> Bool
switch Natural
bs (a
x : [a]
xs)
| Bool -> Bool
switch (Natural
bs Natural -> Int -> Bool
forall a. Bits a => a -> Int -> Bool
`testBit` Int
0) = let ([a]
zs, (Natural
bs', [a]
zzs)) = (Bool -> Bool) -> Natural -> [a] -> ([a], (Natural, [a]))
forall a. (Bool -> Bool) -> Natural -> [a] -> ([a], (Natural, [a]))
spanBits Bool -> Bool
switch (Natural
bs Natural -> Int -> Natural
forall a. Bits a => a -> Int -> a
`shiftR` Int
1) [a]
xs in (a
x a -> [a] -> [a]
forall a. a -> [a] -> [a]
: [a]
zs, (Natural
bs', [a]
zzs))
| Bool
otherwise = ([], (Natural
bs, a
x a -> [a] -> [a]
forall a. a -> [a] -> [a]
: [a]
xs))
partitionFromBits :: Natural -> [a] -> [[a]]
partitionFromBits :: Natural -> [a] -> [[a]]
partitionFromBits Natural
_ [] = []
partitionFromBits Natural
bs [a]
xs =
let switch :: Bool -> Bool
switch = if Natural
bs Natural -> Int -> Bool
forall a. Bits a => a -> Int -> Bool
`testBit` Int
0 then Bool -> Bool
forall a. a -> a
id else Bool -> Bool
not
([a]
ys, (Natural
bs', [a]
yss)) = (Bool -> Bool) -> Natural -> [a] -> ([a], (Natural, [a]))
forall a. (Bool -> Bool) -> Natural -> [a] -> ([a], (Natural, [a]))
spanBits Bool -> Bool
switch Natural
bs [a]
xs
in [a]
ys [a] -> [[a]] -> [[a]]
forall a. a -> [a] -> [a]
: Natural -> [a] -> [[a]]
forall a. Natural -> [a] -> [[a]]
partitionFromBits Natural
bs' [a]
yss
partitionLengths :: Word -> Int -> [Int]
partitionLengths :: Word -> Int -> [Int]
partitionLengths Word
bs = Word -> Int -> Int -> [Int]
forall b. FiniteBits b => b -> Int -> Int -> [Int]
op Word
bs (Word -> Int
forall b. FiniteBits b => b -> Int
countTrailingZeros Word
bs)
where
op :: b -> Int -> Int -> [Int]
op b
b Int
0 Int
m = let b' :: b
b' = b -> b
forall a. Bits a => a -> a
complement b
b in b -> Int -> Int -> [Int]
op b
b' (b -> Int
forall b. FiniteBits b => b -> Int
countTrailingZeros b
b') Int
m
op b
b Int
z Int
m =
if Int
z Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
m
then [Int
m | Int
m Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0]
else
let b' :: b
b' = b
b b -> Int -> b
forall a. Bits a => a -> Int -> a
`shiftR` Int
z
in Int
z Int -> [Int] -> [Int]
forall a. a -> [a] -> [a]
: b -> Int -> Int -> [Int]
op b
b' (b -> Int
forall b. FiniteBits b => b -> Int
countTrailingZeros b
b') (Int
m Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
z)
partitionFromBitsThin :: ([a] -> Bool) -> Natural -> [a] -> Maybe [[a]]
partitionFromBitsThin :: ([a] -> Bool) -> Natural -> [a] -> Maybe [[a]]
partitionFromBitsThin [a] -> Bool
_ Natural
_ [] = [[a]] -> Maybe [[a]]
forall a. a -> Maybe a
Just []
partitionFromBitsThin [a] -> Bool
r Natural
bs [a]
xs =
let ps :: [[a]]
ps = Natural -> [a] -> [[a]]
forall a. Natural -> [a] -> [[a]]
partitionFromBits Natural
bs [a]
xs
in Bool -> Maybe ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (([a] -> Bool) -> [[a]] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all [a] -> Bool
r [[a]]
ps) Maybe () -> Maybe [[a]] -> Maybe [[a]]
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> [[a]] -> Maybe [[a]]
forall (f :: * -> *) a. Applicative f => a -> f a
pure [[a]]
ps
uniformPartitionThinN ::
(StatefulGen g m) =>
Int ->
Int ->
([a] -> Bool) ->
[a] ->
g ->
m (Maybe [[a]])
uniformPartitionThinN :: Int -> Int -> ([a] -> Bool) -> [a] -> g -> m (Maybe [[a]])
uniformPartitionThinN Int
maxit Int
_ [a] -> Bool
_ [a]
_ g
_ | Int
maxit Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
0 = Maybe [[a]] -> m (Maybe [[a]])
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe [[a]]
forall a. Maybe a
Nothing
uniformPartitionThinN Int
maxit Int
n [a] -> Bool
r [a]
xs g
g = do
Natural
bs <- (Natural, Natural) -> g -> m Natural
forall a g (m :: * -> *).
(UniformRange a, StatefulGen g m) =>
(a, a) -> g -> m a
uniformRM (Natural
0, Natural
2 Natural -> Int -> Natural
forall a b. (Num a, Integral b) => a -> b -> a
^ Int
n Natural -> Natural -> Natural
forall a. Num a => a -> a -> a
- Natural
1) g
g
case ([a] -> Bool) -> Natural -> [a] -> Maybe [[a]]
forall a. ([a] -> Bool) -> Natural -> [a] -> Maybe [[a]]
partitionFromBitsThin [a] -> Bool
r Natural
bs [a]
xs of
Maybe [[a]]
Nothing -> Int -> Int -> ([a] -> Bool) -> [a] -> g -> m (Maybe [[a]])
forall g (m :: * -> *) a.
StatefulGen g m =>
Int -> Int -> ([a] -> Bool) -> [a] -> g -> m (Maybe [[a]])
uniformPartitionThinN (Int
maxit Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1) Int
n [a] -> Bool
r [a]
xs g
g
Just [[a]]
ys -> Maybe [[a]] -> m (Maybe [[a]])
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Maybe [[a]] -> m (Maybe [[a]])) -> Maybe [[a]] -> m (Maybe [[a]])
forall a b. (a -> b) -> a -> b
$ [[a]] -> Maybe [[a]]
forall a. a -> Maybe a
Just [[a]]
ys
uniformPartition :: (StatefulGen g m) => [a] -> g -> m [[a]]
uniformPartition :: [a] -> g -> m [[a]]
uniformPartition [a]
xs g
g = do
let d :: Int
d = [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [a]
xs
Natural
bs <- (Natural, Natural) -> g -> m Natural
forall a g (m :: * -> *).
(UniformRange a, StatefulGen g m) =>
(a, a) -> g -> m a
uniformRM (Natural
0, Natural
2 Natural -> Int -> Natural
forall a b. (Num a, Integral b) => a -> b -> a
^ Int
d Natural -> Natural -> Natural
forall a. Num a => a -> a -> a
- Natural
1) g
g
[[a]] -> m [[a]]
forall (f :: * -> *) a. Applicative f => a -> f a
pure ([[a]] -> m [[a]]) -> [[a]] -> m [[a]]
forall a b. (a -> b) -> a -> b
$ Natural -> [a] -> [[a]]
forall a. Natural -> [a] -> [[a]]
partitionFromBits Natural
bs [a]
xs
uniformPartitionThin ::
(StatefulGen g m) =>
Int ->
([a] -> Bool) ->
[a] ->
g ->
m (Maybe [[a]])
uniformPartitionThin :: Int -> ([a] -> Bool) -> [a] -> g -> m (Maybe [[a]])
uniformPartitionThin Int
maxit [a] -> Bool
r [a]
xs = Int -> Int -> ([a] -> Bool) -> [a] -> g -> m (Maybe [[a]])
forall g (m :: * -> *) a.
StatefulGen g m =>
Int -> Int -> ([a] -> Bool) -> [a] -> g -> m (Maybe [[a]])
uniformPartitionThinN Int
maxit ([a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [a]
xs) [a] -> Bool
r [a]
xs