2 Module : Gargantext.Prelude
4 Copyright : (c) CNRS, 2017-Present
5 License : AGPL + CECILL v3
6 Maintainer : team@gargantext.org
7 Stability : experimental
10 Here is a longer description of this module, containing some
11 commentary with @some markup@.
14 {-# OPTIONS_GHC -fno-warn-name-shadowing #-}
15 {-# OPTIONS_GHC -fno-warn-type-defaults #-}
17 {-# LANGUAGE NoImplicitPrelude #-}
19 module Gargantext.Prelude
20 ( module Gargantext.Prelude
31 import GHC.Exts (sortWith)
33 import Data.Maybe (isJust, fromJust, maybe)
34 import Protolude ( Bool(True, False), Int, Double, Integer
35 , Fractional, Num, Maybe(Just,Nothing)
36 , Enum, Bounded, Float
38 , pure, (>>=), (=<<), (<*>), (<$>), panic
41 , Ord, Integral, Foldable, RealFrac, Monad, filter
42 , reverse, map, mapM, zip, drop, take, zipWith
43 , sum, fromIntegral, length, fmap, foldl, foldl'
44 , takeWhile, sqrt, undefined, identity
45 , abs, min, max, maximum, minimum, return, snd, truncate
46 , (+), (*), (/), (-), (.), ($), (&), (**), (^), (<), (>), log
47 , Eq, (==), (>=), (<=), (<>), (/=)
48 , (&&), (||), not, any
50 , elem, die, mod, div, const, either
51 , curry, uncurry, repeat
59 -- TODO import functions optimized in Utils.Count
60 -- import Protolude hiding (head, last, all, any, sum, product, length)
61 -- import Gargantext.Utils.Count
62 import qualified Data.List as L hiding (head, sum)
63 import qualified Control.Monad as M
66 import qualified Data.Map as M
68 import Data.Map.Strict (insertWith)
69 import qualified Data.Vector as V
71 import Text.Show (Show(), show)
72 import Text.Read (Read())
73 import Data.String.Conversions (cs)
75 --pf :: (a -> Bool) -> [a] -> [a]
81 --pm :: (a -> b) -> [a] -> [b]
84 map2 :: (t -> b) -> [[t]] -> [[b]]
85 map2 fun = map (map fun)
87 -- Exponential Average
88 eavg :: [Double] -> Double
89 eavg (x:xs) = a*x + (1-a)*(eavg xs)
94 mean :: Fractional a => [a] -> a
95 mean xs = if L.null xs then 0.0
96 else sum xs / fromIntegral (length xs)
98 sumMaybe :: Num a => [Maybe a] -> Maybe a
99 sumMaybe = fmap sum . M.sequence
101 variance :: Floating a => [a] -> a
102 variance xs = mean $ map (\x -> (x - m) ** 2) xs where
105 deviation :: [Double] -> Double
106 deviation = sqrt . variance
108 movingAverage :: Fractional b => Int -> [b] -> [b]
109 movingAverage steps xs = map mean $ chunkAlong steps 1 xs
111 ma :: [Double] -> [Double]
114 -- | splitEvery n == chunkAlong n n
115 splitEvery :: Int -> [a] -> [[a]]
118 let (h,t) = L.splitAt n xs
119 in h : splitEvery n t
121 -- | Function to split a range into chunks
122 chunkAlong :: Int -> Int -> [a] -> [[a]]
123 chunkAlong a b l = only (while dropAlong)
126 while = takeWhile (\x -> length x >= a)
127 dropAlong = L.scanl (\x _y -> drop b x) l ([1..] :: [Integer])
129 -- | Optimized version (Vector)
130 chunkAlong' :: Int -> Int -> V.Vector a -> V.Vector (V.Vector a)
131 chunkAlong' a b l = only (while dropAlong)
133 only = V.map (V.take a)
134 while = V.takeWhile (\x -> V.length x >= a)
135 dropAlong = V.scanl (\x _y -> V.drop b x) l (V.fromList [1..])
137 -- | TODO Inverse of chunk ? unchunkAlong ?
138 unchunkAlong :: Int -> Int -> [[a]] -> [a]
139 unchunkAlong = undefined
142 -- splitAlong [2,3,4] ("helloworld" :: [Char]) == ["he", "llo", "worl", "d"]
143 splitAlong :: [Int] -> [Char] -> [[Char]]
144 splitAlong _ [] = [] -- No list? done
145 splitAlong [] xs = [xs] -- No place to split at? Return the remainder
146 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
148 takeWhileM :: (Monad m) => (a -> Bool) -> [m a] -> m [a]
149 takeWhileM _ [] = return []
150 takeWhileM p (a:as) = do
154 vs <- takeWhileM p as
159 -- To select the right algorithme according to the type:
160 -- https://github.com/mikeizbicki/ifcxt
162 sumSimple :: Num a => [a] -> a
163 sumSimple = L.foldl' (+) 0
165 -- | https://en.wikipedia.org/wiki/Kahan_summation_algorithm
166 sumKahan :: Num a => [a] -> a
167 sumKahan = snd . L.foldl' go (0,0)
169 go (c,t) i = ((t'-t)-y,t')
174 -- | compute part of the dict
175 count2map :: (Ord k, Foldable t) => t k -> Map k Double
176 count2map xs = M.map (/ (fromIntegral (length xs))) (count2map' xs)
178 -- | insert in a dict
179 count2map' :: (Ord k, Foldable t) => t k -> Map k Double
180 count2map' xs = L.foldl' (\x y -> insertWith (+) y 1 x) M.empty xs
183 trunc :: (RealFrac a, Integral c, Integral b) => b -> a -> c
184 trunc n = truncate . (* 10^n)
186 trunc' :: Int -> Double -> Double
187 trunc' n x = fromIntegral $ truncate $ (x * 10^n)
190 bool2int :: Num a => Bool -> a
191 bool2int b = case b of
195 bool2double :: Bool -> Double
196 bool2double bool = case bool of
202 -- Normalizing && scaling data
203 scale :: [Double] -> [Double]
206 scaleMinMax :: [Double] -> [Double]
207 scaleMinMax xs = map (\x -> (x - mi / (ma - mi + 1) )) xs'
213 scaleNormalize :: [Double] -> [Double]
214 scaleNormalize xs = map (\x -> (x - v / (m + 1))) xs'
222 normalize :: [Double] -> [Double]
223 normalize as = normalizeWith identity as
225 normalizeWith :: Fractional b => (a -> b) -> [a] -> [b]
226 normalizeWith extract bs = map (\x -> x/(sum bs')) bs'
230 -- Zip functions to add
231 zipFst :: ([b] -> [a]) -> [b] -> [(a, b)]
232 zipFst f xs = zip (f xs) xs
234 zipSnd :: ([a] -> [b]) -> [a] -> [(a, b)]
235 zipSnd f xs = zip xs (f xs)
238 unMaybe :: [Maybe a] -> [a]
239 unMaybe = map fromJust . L.filter isJust
242 maximumWith f = L.maximumBy (compare `on` f)