module Persistence.Util where
import Data.List as L
import Data.Vector as V
import Control.Parallel.Strategies
instance Num Bool where
p + q = p `xor` q
p * q = p && q
p - q = p `xor` (not q)
negate = not
abs = id
fromInteger 0 = False
fromInteger _ = True
signum bool = if bool then 1 else 0
xor :: Bool -> Bool -> Bool
xor False False = False
xor True False = True
xor False True = True
xor True True = False
one (a, _, _) = a
two (_, b, _) = b
thr (_, _, c) = c
not1 (_, b, c) = (b, c)
not2 (a, _, c) = (a, c)
not3 (a, b, _) = (a, b)
flatten :: Vector (Vector a) -> Vector a
flatten = V.foldl1 (V.++)
mul :: Num a => a -> Vector a -> Vector a
mul s = V.map (*s)
add :: Num a => Vector a -> Vector a -> Vector a
add = V.zipWith (+)
subtr :: Num a => Vector a -> Vector a -> Vector a
subtr = V.zipWith (\x y -> x - y)
dotProduct :: Num a => Vector a -> Vector a -> a
dotProduct vec1 vec2
| a && b = fromIntegral 0
| a = error "Persistence.Util.dotProduct (first argument too short). This is a bug. Please email the Persistence maintainers."
| b = error "Persistence.Util.dotProduct (second argument too short). This is a bug. Please email the Persistence maintainers."
| otherwise = (V.head vec1)*(V.head vec2) + (dotProduct (V.tail vec1) (V.tail vec2))
where a = V.null vec1; b = V.null vec2
extEucAlg :: Integral a => a -> a -> (a, a, a)
extEucAlg a b =
let eeaHelper r s t =
case snd r of
0 -> (fst r, fst s, fst t)
_ ->
let r1 = fst r
r2 = snd r
s2 = snd s
t2 = snd t
q = r1 `div` r2
nextr = r1 - q*r2
nexts = fst s - q*s2
nextt = fst t - q*t2
in eeaHelper (r2, nextr) (s2, nexts) (t2, nextt)
in (\(x, y, z) -> if x < 0 then (-x, -y, -z) else (x, y, z)) $ eeaHelper (a, b) (0, 1) (1, 0)
divides :: Int -> Int -> Bool
0 `divides` b = False
a `divides` b
| b < 0 = False
| b == 0 = True
| otherwise = a `divides` (b - (abs a))
switchElems ::Int -> Int -> Vector a -> Vector a
switchElems i j vector
| j == i = vector
| j < i =
let first = V.take j vector
second = V.drop (j + 1) (V.take i vector)
third = V.drop (i + 1) vector
in first V.++ (cons (vector ! i) second) V.++ (cons (vector ! j) third)
| otherwise =
let first = V.take i vector
second = V.drop (i + 1) (V.take j vector)
third = V.drop (j + 1) vector
in first V.++ (cons (vector ! j) second) V.++ (cons (vector ! i) third)
rmIndex :: Int -> Vector a -> Vector a
rmIndex i v = (V.take i v) V.++ (V.drop (i + 1) v)
range :: Int -> Int -> Vector Int
range x y
| x == y = x `cons` empty
| x < y = x `cons` (range (x + 1) y)
| x > y = (range x (y + 1)) `snoc` y
getCombos :: Vector a -> Vector (Vector a)
getCombos vector = V.map (\i -> rmIndex i vector) $ 0 `range` (V.length vector - 1)
dropRightWhile :: (a -> Bool) -> Vector a -> Vector a
dropRightWhile p v = if p (V.last v) then dropRightWhile p (V.init v) else v
filterWithIndex :: (Int -> a -> Bool) -> Vector a -> Vector a
filterWithIndex p vector =
let maxIndex = V.length vector - 1
calc i
| i == maxIndex = V.empty
| p i (vector ! i) = (vector ! i) `cons` calc (i + 1)
| otherwise = calc (i + 1)
in calc 0
mapWithIndex :: (Int -> a -> b) -> Vector a -> Vector b
mapWithIndex f vector =
let helper i vec =
if V.null vec then empty
else cons (f i $ V.head vec) $ helper (i + 1) (V.tail vec)
in helper 0 vector
parMapVec :: (a -> b) -> Vector a -> Vector b
parMapVec f = runEval . (evalTraversable rpar) . (V.map f)
parMapWithIndex :: (Int -> a -> b) -> Vector a -> Vector b
parMapWithIndex f = runEval . (evalTraversable rpar) . (mapWithIndex f)
elemAndIndex :: (a -> Bool) -> Vector a -> Maybe (a, Int)
elemAndIndex p vector =
let helper i vec
| V.null vec = Nothing
| p $ V.head vec = Just (V.head vec, i)
| otherwise = helper (i + 1) $ V.tail vec
in helper 0 vector
elemAndIndices :: (a -> Bool) -> Vector a -> [(a, Int)]
elemAndIndices p vector =
let helper i vec
| V.null vec = []
| p $ V.head vec = (V.head vec, i) : (helper (i + 1) $ V.tail vec)
| otherwise = helper (i + 1) $ V.tail vec
in helper 0 vector
findBothElems :: (a -> b -> Bool) -> Vector a -> Vector b -> Vector (a, b)
findBothElems rel vector1 vector2 =
let len = V.length vector1
calc i result =
let a = vector1 ! i
in
if i == len then result
else case V.find (\b -> rel a b) vector2 of
Just b -> calc (i + 1) $ result `snoc` (a, b)
Nothing -> calc (i + 1) result
in calc 0 V.empty
sortVecs :: [Vector a] -> [Vector a]
sortVecs [] = []
sortVecs (v:vs) =
let len = V.length v
less = sortVecs $ L.filter (\u -> V.length u < len) vs
more = sortVecs $ L.filter (\u -> V.length u >= len) vs
in more L.++ [v] L.++ less
replaceElem :: Int -> a -> Vector a -> Vector a
replaceElem i e v = (V.take i v) V.++ (e `cons` (V.drop (i + 1) v))
replaceElemList :: Int -> a -> [a] -> [a]
replaceElemList i e l = (L.take i l) L.++ (e:(L.drop (i + 1) l))
quickSort :: (a -> a -> Bool) -> Vector a -> Vector a
quickSort rel vector =
if V.null vector then empty
else
let x = V.head vector
xs = V.tail vector
greater = V.filter (rel x) xs
lesser = V.filter (not . (rel x)) xs
in (quickSort rel greater) V.++ (x `cons` (quickSort rel lesser))
orderedInsert :: (a -> a -> Bool) -> a -> Vector a -> Vector a
orderedInsert rel x vector =
case V.findIndex (\y -> y `rel` x) vector of
Just i ->
case V.findIndex (\y -> x `rel` y) $ V.drop i vector of
Just j -> (V.take (i + j) vector) V.++ (x `cons` (V.drop (i + j) vector))
Nothing -> (V.take i vector) V.++ (x `cons` (V.drop i vector))
Nothing -> vector `snoc` x
bigU :: Eq a => Vector (Vector a) -> Vector a
bigU =
let exists x v
| V.null v = False
| V.head v == x = True
| otherwise = exists x (V.tail v)
union v1 v2 =
if V.null v1 then v2
else
let x = V.head v1
in
if exists x v2 then union (V.tail v1) v2
else union (V.tail v1) (x `cons` v2)
in V.foldl1 union
binarySearch :: Ord a => a -> Vector a -> Int -> Int -> Maybe Int
binarySearch value xs low high
| high < low = Nothing
| xs ! mid > value = binarySearch value xs low (mid - 1)
| xs ! mid < value = binarySearch value xs (mid + 1) high
| otherwise = Just mid
where mid = low + ((high - low) `div` 2)
(|^|) :: Ord a => Vector a -> Vector a -> Vector a
vector1 |^| vector2 =
let len = V.length vector2 - 1
calc acc v =
if V.null v then acc
else
let x = V.head v; xs = V.tail v
in case binarySearch x vector2 0 len of
Just _ -> calc (x `cons` acc) xs
Nothing -> calc acc xs
in calc V.empty vector1
smartSnoc :: Eq a => Vector a -> a -> Vector a
smartSnoc v e =
case V.elemIndex e v of
Just _ -> v
Nothing -> v `snoc` e
foldRelation :: (a -> a -> Bool) -> Vector a -> a
foldRelation rel vec =
let calc w v
| V.null v = w
| rel w x = calc x xs
| otherwise = calc w xs
where x = V.head v; xs = V.tail v
in calc (V.head vec) (V.tail vec)
elemIndexUnsafe :: Eq a => a -> Vector a -> Int
elemIndexUnsafe elem vector =
let find i v
| V.null v = error "Persistence.Util.elemIndexUnsafe. This is a bug. Please email the Persistence maintainers."
| V.head v == elem = i
| otherwise = find (i + 1) $ V.tail v
in find 0 vector
evalPar :: a -> [a] -> [a]
evalPar c r = runEval $ rpar c >> rseq r >> return (c:r)
uin :: Ord a => Vector a -> Vector a -> Vector a
u `uin` v =
let len = V.length v
findAndInsert i elem vec
| i == len = vec `snoc` elem
| elem == x = (V.take i vec) V.++ (V.drop i1 vec)
| elem > x = (V.take i vec) V.++ (elem `cons` (V.drop i vec))
| otherwise = findAndInsert i1 elem vec
where x = vec ! i; i1 = i + 1
in
if V.null u then v
else (V.tail u) `uin` (findAndInsert 0 (V.head u) v)