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