]> Git — Sourcephile - gargantext.git/blob - src/Gargantext/Prelude.hs
[PROTOLUDE] cleaning filter.
[gargantext.git] / src / Gargantext / Prelude.hs
1 {-# OPTIONS_GHC -fno-warn-name-shadowing #-}
2 {-# OPTIONS_GHC -fno-warn-type-defaults #-}
3 {-# LANGUAGE NoImplicitPrelude #-}
4
5 {-
6 TODO: import head impossible from Protolude: why ?
7 -}
8
9 module Gargantext.Prelude
10 ( module Gargantext.Prelude
11 , module Protolude
12 , headMay
13 )
14 where
15
16 import Protolude ( Bool(True, False), Int, Double, Integer
17 , Fractional, Num, Maybe(Just,Nothing)
18 , Floating, Char, IO
19 , pure, (<$>), panic
20 , Ord, Integral, Foldable, RealFrac, Monad, filter
21 , reverse, map, zip, drop, take, zipWith
22 , sum, fromIntegral, length, fmap
23 , takeWhile, sqrt, undefined, identity
24 , abs, maximum, minimum, return, snd, truncate
25 , (+), (*), (/), (-), (.), (>=), ($), (**), (^)
26 )
27
28 -- TODO import functions optimized in Utils.Count
29 -- import Protolude hiding (head, last, all, any, sum, product, length)
30 -- import Gargantext.Utils.Count
31
32 import qualified Data.List as L hiding (head, sum)
33 import qualified Control.Monad as M
34 import qualified Data.Map as Map
35 import qualified Data.Vector as V
36 import Safe (headMay)
37
38 --pf :: (a -> Bool) -> [a] -> [a]
39 --pf = filter
40
41 pr :: [a] -> [a]
42 pr = reverse
43
44 --pm :: (a -> b) -> [a] -> [b]
45 --pm = map
46
47 map2 :: (t -> b) -> [[t]] -> [[b]]
48 map2 fun = map (map fun)
49
50 pz :: [a] -> [b] -> [(a, b)]
51 pz = zip
52
53 pd :: Int -> [a] -> [a]
54 pd = drop
55
56 ptk :: Int -> [a] -> [a]
57 ptk = take
58
59 pzw :: (a -> b -> c) -> [a] -> [b] -> [c]
60 pzw = zipWith
61
62 -- Exponential Average
63 eavg :: [Double] -> Double
64 eavg (x:xs) = a*x + (1-a)*(eavg xs)
65 where a = 0.70
66 eavg [] = 0
67
68 -- Simple Average
69 mean :: Fractional a => [a] -> a
70 mean xs = if L.null xs then 0.0
71 else sum xs / fromIntegral (length xs)
72
73 sumMaybe :: Num a => [Maybe a] -> Maybe a
74 sumMaybe = fmap sum . M.sequence
75
76 variance :: Floating a => [a] -> a
77 variance xs = mean $ map (\x -> (x - m) ** 2) xs where
78 m = mean xs
79
80 deviation :: [Double] -> Double
81 deviation = sqrt . variance
82
83 movingAverage :: Fractional b => Int -> [b] -> [b]
84 movingAverage steps xs = map mean $ chunkAlong steps 1 xs
85
86 ma :: [Double] -> [Double]
87 ma = movingAverage 3
88
89
90 -- | Function to split a range into chunks
91 chunkAlong :: Int -> Int -> [a] -> [[a]]
92 chunkAlong a b l = only (while dropAlong)
93 where
94 only = map (take a)
95 while = takeWhile (\x -> length x >= a)
96 dropAlong = L.scanl (\x _y -> drop b x) l ([1..] :: [Integer])
97
98 -- | Optimized version (Vector)
99 chunkAlong' :: Int -> Int -> V.Vector a -> V.Vector (V.Vector a)
100 chunkAlong' a b l = only (while dropAlong)
101 where
102 only = V.map (V.take a)
103 while = V.takeWhile (\x -> V.length x >= a)
104 dropAlong = V.scanl (\x _y -> V.drop b x) l (V.fromList [1..])
105
106 -- | TODO Inverse of chunk ? unchunkAlong ?
107 unchunkAlong :: Int -> Int -> [[a]] -> [a]
108 unchunkAlong = undefined
109
110
111 -- splitAlong [2,3,4] ("helloworld" :: [Char]) == ["he", "llo", "worl", "d"]
112 splitAlong :: [Int] -> [Char] -> [[Char]]
113 splitAlong _ [] = [] -- No list? done
114 splitAlong [] xs = [xs] -- No place to split at? Return the remainder
115 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
117 takeWhileM :: (Monad m) => (a -> Bool) -> [m a] -> m [a]
118 takeWhileM _ [] = return []
119 takeWhileM p (a:as) = do
120 v <- a
121 if p v
122 then do
123 vs <- takeWhileM p as
124 return (v:vs)
125 else return []
126
127 -- SUMS
128 -- To select the right algorithme according to the type:
129 -- https://github.com/mikeizbicki/ifcxt
130
131 sumSimple :: Num a => [a] -> a
132 sumSimple = L.foldl' (+) 0
133
134 -- | https://en.wikipedia.org/wiki/Kahan_summation_algorithm
135 sumKahan :: Num a => [a] -> a
136 sumKahan = snd . L.foldl' go (0,0)
137 where
138 go (c,t) i = ((t'-t)-y,t')
139 where
140 y = i-c
141 t' = t+y
142
143 -- | compute part of the dict
144 count2map :: (Ord k, Foldable t) => t k -> Map.Map k Double
145 count2map xs = Map.map (/ (fromIntegral (length xs))) (count2map' xs)
146
147 -- | insert in a dict
148 count2map' :: (Ord k, Foldable t) => t k -> Map.Map k Double
149 count2map' xs = L.foldl' (\x y -> Map.insertWith' (+) y 1 x) Map.empty xs
150
151
152 trunc :: (RealFrac a, Integral c, Integral b) => b -> a -> c
153 trunc n = truncate . (* 10^n)
154
155 trunc' :: Int -> Double -> Double
156 trunc' n x = fromIntegral $ truncate $ (x * 10^n)
157
158
159 bool2int :: Num a => Bool -> a
160 bool2int b = case b of
161 True -> 1
162 False -> 0
163
164 bool2double :: Bool -> Double
165 bool2double bool = case bool of
166 True -> 1.0
167 False -> 0.0
168
169
170
171 -- Normalizing && scaling data
172 scale :: [Double] -> [Double]
173 scale = scaleMinMax
174
175 scaleMinMax :: [Double] -> [Double]
176 scaleMinMax xs = map (\x -> (x - mi / (ma - mi + 1) )) xs'
177 where
178 ma = maximum xs'
179 mi = minimum xs'
180 xs' = map abs xs
181
182 scaleNormalize :: [Double] -> [Double]
183 scaleNormalize xs = map (\x -> (x - v / (m + 1))) xs'
184 where
185 v = variance xs'
186 m = mean xs'
187 xs' = map abs xs
188
189
190
191 normalize :: [Double] -> [Double]
192 normalize as = normalizeWith identity as
193
194 normalizeWith :: Fractional b => (a -> b) -> [a] -> [b]
195 normalizeWith extract bs = map (\x -> x/(sum bs')) bs'
196 where
197 bs' = map extract bs
198
199 -- Zip functions to add
200 zipFst :: ([b] -> [a]) -> [b] -> [(a, b)]
201 zipFst f xs = zip (f xs) xs
202
203 zipSnd :: ([a] -> [b]) -> [a] -> [(a, b)]
204 zipSnd f xs = zip xs (f xs)