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