1 {-# OPTIONS_GHC -fno-warn-name-shadowing #-}
2 {-# OPTIONS_GHC -fno-warn-type-defaults #-}
3 {-# LANGUAGE NoImplicitPrelude #-}
6 TODO: import head impossible from Protolude: why ?
9 module Data.Gargantext.Prelude
10 ( module Data.Gargantext.Prelude
16 import Protolude ( Bool(True, False), Int, Double, Integer
17 , Fractional, Num, Maybe, Floating, Char
18 , Ord, Integral, Foldable, RealFrac, Monad, filter
19 , reverse, map, zip, drop, take, zipWith
20 , sum, fromIntegral, length, fmap
21 , takeWhile, sqrt, undefined, identity
22 , abs, maximum, minimum, return, snd, truncate
23 , (+), (*), (/), (-), (.), (>=), ($), (**), (^)
26 -- TODO import functions optimized in Utils.Count
27 -- import Protolude hiding (head, last, all, any, sum, product, length)
28 -- import Data.Gargantext.Utils.Count
30 import qualified Data.List as L hiding (head, sum)
31 import qualified Control.Monad as M
32 import qualified Data.Map as Map
33 import qualified Data.Vector as V
37 pf :: (a -> Bool) -> [a] -> [a]
43 pm :: (a -> b) -> [a] -> [b]
46 pm2 :: (t -> b) -> [[t]] -> [[b]]
49 pz :: [a] -> [b] -> [(a, b)]
52 pd :: Int -> [a] -> [a]
55 ptk :: Int -> [a] -> [a]
58 pzw :: (a -> b -> c) -> [a] -> [b] -> [c]
61 -- Exponential Average
62 eavg :: [Double] -> Double
63 eavg (x:xs) = a*x + (1-a)*(eavg xs)
68 mean :: Fractional a => [a] -> a
69 mean xs = if L.null xs then 0.0
70 else sum xs / fromIntegral (length xs)
72 sumMaybe :: Num a => [Maybe a] -> Maybe a
73 sumMaybe = fmap sum . M.sequence
75 variance :: Floating a => [a] -> a
76 variance xs = mean $ pm (\x -> (x - m) ** 2) xs where
79 deviation :: [Double] -> Double
80 deviation = sqrt . variance
82 movingAverage :: Fractional b => Int -> [b] -> [b]
83 movingAverage steps xs = pm mean $ chunkAlong steps 1 xs
85 ma :: [Double] -> [Double]
89 -- | Function to split a range into chunks
90 chunkAlong :: Int -> Int -> [a] -> [[a]]
91 chunkAlong a b l = only (while dropAlong)
94 while = takeWhile (\x -> length x >= a)
95 dropAlong = L.scanl (\x _y -> drop b x) l ([1..] :: [Integer])
97 -- | Optimized version (Vector)
98 chunkAlong' :: Int -> Int -> V.Vector a -> V.Vector (V.Vector a)
99 chunkAlong' a b l = only (while dropAlong)
101 only = V.map (V.take a)
102 while = V.takeWhile (\x -> V.length x >= a)
103 dropAlong = V.scanl (\x _y -> V.drop b x) l (V.fromList [1..])
105 -- | TODO Inverse of chunk ? unchunkAlong ?
106 unchunkAlong :: Int -> Int -> [[a]] -> [a]
107 unchunkAlong = undefined
110 -- splitAlong [2,3,4] ("helloworld" :: [Char]) == ["he", "llo", "worl", "d"]
111 splitAlong :: [Int] -> [Char] -> [[Char]]
112 splitAlong _ [] = [] -- No list? done
113 splitAlong [] xs = [xs] -- No place to split at? Return the remainder
114 splitAlong (x:xs) ys = take x ys : splitAlong xs (drop x ys) -- take until our split spot, recurse with next split spot and list remainder
116 takeWhileM :: (Monad m) => (a -> Bool) -> [m a] -> m [a]
117 takeWhileM _ [] = return []
118 takeWhileM p (a:as) = do
122 vs <- takeWhileM p as
127 -- To select the right algorithme according to the type:
128 -- https://github.com/mikeizbicki/ifcxt
130 sumSimple :: Num a => [a] -> a
131 sumSimple = L.foldl' (+) 0
133 -- | https://en.wikipedia.org/wiki/Kahan_summation_algorithm
134 sumKahan :: Num a => [a] -> a
135 sumKahan = snd . L.foldl' go (0,0)
137 go (c,t) i = ((t'-t)-y,t')
142 -- | compute part of the dict
143 count2map :: (Ord k, Foldable t) => t k -> Map.Map k Double
144 count2map xs = Map.map (/ (fromIntegral (length xs))) (count2map' xs)
146 -- | insert in a dict
147 count2map' :: (Ord k, Foldable t) => t k -> Map.Map k Double
148 count2map' xs = L.foldl' (\x y -> Map.insertWith' (+) y 1 x) Map.empty xs
151 trunc :: (RealFrac a, Integral c, Integral b) => b -> a -> c
152 trunc n = truncate . (* 10^n)
154 trunc' :: Int -> Double -> Double
155 trunc' n x = fromIntegral $ truncate $ (x * 10^n)
158 bool2int :: Num a => Bool -> a
159 bool2int b = case b of
163 bool2double :: Bool -> Double
164 bool2double bool = case bool of
170 -- Normalizing && scaling data
171 scale :: [Double] -> [Double]
174 scaleMinMax :: [Double] -> [Double]
175 scaleMinMax xs = pm (\x -> (x - mi / (ma - mi + 1) )) xs'
181 scaleNormalize :: [Double] -> [Double]
182 scaleNormalize xs = pm (\x -> (x - v / (m + 1))) xs'
190 normalize :: [Double] -> [Double]
191 normalize as = normalizeWith identity as
193 normalizeWith :: Fractional b => (a -> b) -> [a] -> [b]
194 normalizeWith extract bs = pm (\x -> x/(sum bs')) bs'
198 -- Zip functions to add
199 zipFst :: ([b] -> [a]) -> [b] -> [(a, b)]
200 zipFst f xs = zip (f xs) xs
202 zipSnd :: ([a] -> [b]) -> [a] -> [(a, b)]
203 zipSnd f xs = zip xs (f xs)