2 Module : Gargantext.Prelude
3 Description : Specific Prelude of the project
4 Copyright : (c) CNRS, 2017-Present
5 License : AGPL + CECILL v3
6 Maintainer : team@gargantext.org
7 Stability : experimental
12 {-# OPTIONS_GHC -fno-warn-name-shadowing #-}
13 {-# OPTIONS_GHC -fno-warn-type-defaults #-}
15 {-# LANGUAGE NoImplicitPrelude #-}
16 {-# LANGUAGE OverloadedStrings #-}
17 {-# LANGUAGE RankNTypes #-}
19 module Gargantext.Prelude
20 ( module Gargantext.Prelude
23 , module GHC.Err.Located
34 import Control.Monad.IO.Class (liftIO, MonadIO)
35 import Control.Concurrent (newEmptyMVar, takeMVar, putMVar, forkIO)
36 import GHC.Exts (sortWith)
37 import GHC.Err.Located (undefined)
38 import GHC.Real (round)
39 import Data.Maybe (isJust, fromJust, maybe)
40 import Data.Text (Text)
41 import Protolude ( Bool(True, False), Int, Int64, Double, Integer
42 , Fractional, Num, Maybe(Just,Nothing)
43 , Enum, Bounded, Float
45 , pure, (>>=), (=<<), (<*>), (<$>), (>>)
48 , Ord, Integral, Foldable, RealFrac, Monad, filter
49 , reverse, map, mapM, zip, drop, take, zipWith
50 , sum, fromIntegral, length, fmap, foldl, foldl'
51 , takeWhile, sqrt, identity
52 , abs, min, max, maximum, minimum, return, snd, truncate
53 , (+), (*), (/), (-), (.), ($), (&), (**), (^), (<), (>), log
54 , Eq, (==), (>=), (<=), (<>), (/=)
55 , (&&), (||), not, any, all
57 , elem, die, mod, div, const, either
58 , curry, uncurry, repeat
66 import Prelude (Enum, Bounded, minBound, maxBound)
67 -- TODO import functions optimized in Utils.Count
68 -- import Protolude hiding (head, last, all, any, sum, product, length)
69 -- import Gargantext.Utils.Count
70 import qualified Data.List as L hiding (head, sum)
71 import qualified Control.Monad as M
74 import qualified Data.Map as M
76 import Data.Map.Strict (insertWith)
77 import qualified Data.Vector as V
78 import Safe (headMay, lastMay, initMay, tailMay)
79 import Text.Show (Show(), show)
80 import Text.Read (Read())
81 import Data.String.Conversions (cs)
84 printDebug :: (Show a, MonadIO m) => [Char] -> a -> m ()
85 printDebug msg x = putStrLn $ msg <> " " <> show x
86 -- printDebug _ _ = pure ()
89 -- | splitEvery n == chunkAlong n n
90 splitEvery :: Int -> [a] -> [[a]]
93 let (h,t) = L.splitAt n xs
99 -- | Function to split a range into chunks
100 -- if step == grain then linearity (splitEvery)
101 -- elif step < grain then overlapping
102 -- else dotted with holes
103 -- TODO FIX BUG if Steps*Grain /= length l
104 -- chunkAlong 10 10 [1..15] == [1..10]
105 -- BUG: what about the rest of (divMod 15 10)?
106 -- TODO: chunkAlongNoRest or chunkAlongWithRest
107 -- default behavior: NoRest
109 chunkAlong :: Eq a => Grain -> Step -> [a] -> [[a]]
110 chunkAlong a b l = case a >= length l of
112 False -> chunkAlong' a b l
114 chunkAlong' :: Eq a => Grain -> Step -> [a] -> [[a]]
115 chunkAlong' a b l = case a > 0 && b > 0 of
116 True -> chunkAlong'' a b l
117 False -> panic "ChunkAlong: Parameters should be > 0 and Grain > Step"
119 chunkAlong'' :: Eq a => Int -> Int -> [a] -> [[a]]
120 chunkAlong'' a b l = filter (/= []) $ only (while dropAlong)
123 while = takeWhile (\x -> length x >= a)
124 dropAlong = L.scanl (\x _y -> drop b x) l ([1..] :: [Integer])
126 -- | Optimized version (Vector)
127 chunkAlongV :: Int -> Int -> V.Vector a -> V.Vector (V.Vector a)
128 chunkAlongV a b l = only (while dropAlong)
130 only = V.map (V.take a)
131 while = V.takeWhile (\x -> V.length x >= a)
132 dropAlong = V.scanl (\x _y -> V.drop b x) l (V.fromList [1..])
134 -- | TODO Inverse of chunk ? unchunkAlong ?
135 -- unchunkAlong :: Int -> Int -> [[a]] -> [a]
136 -- unchunkAlong = undefined
139 -- splitAlong [2,3,4] ("helloworld" :: [Char]) == ["he", "llo", "worl", "d"]
140 splitAlong :: [Int] -> [Char] -> [[Char]]
141 splitAlong _ [] = [] -- No list? done
142 splitAlong [] xs = [xs] -- No place to split at? Return the remainder
143 splitAlong (x:xs) ys = take x ys : splitAlong xs (drop x ys)
144 -- take until our split spot, recurse with next split spot and list remainder
146 takeWhileM :: (Monad m) => (a -> Bool) -> [m a] -> m [a]
147 takeWhileM _ [] = return []
148 takeWhileM p (a:as) = do
152 vs <- takeWhileM p as
157 -- To select the right algorithme according to the type:
158 -- https://github.com/mikeizbicki/ifcxt
160 sumSimple :: Num a => [a] -> a
161 sumSimple = L.foldl' (+) 0
163 -- | https://en.wikipedia.org/wiki/Kahan_summation_algorithm
164 sumKahan :: Num a => [a] -> a
165 sumKahan = snd . L.foldl' go (0,0)
167 go (c,t) i = ((t'-t)-y,t')
172 -- | compute part of the dict
173 count2map :: (Ord k, Foldable t) => t k -> Map k Double
174 count2map xs = M.map (/ (fromIntegral (length xs))) (count2map' xs)
176 -- | insert in a dict
177 count2map' :: (Ord k, Foldable t) => t k -> Map k Double
178 count2map' xs = L.foldl' (\x y -> insertWith (+) y 1 x) M.empty xs
180 trunc :: (RealFrac a, Integral c, Integral b) => b -> a -> c
181 trunc n = truncate . (* 10^n)
183 trunc' :: Int -> Double -> Double
184 trunc' n x = fromIntegral $ truncate $ (x * 10^n)
186 ------------------------------------------------------------------------
187 bool2num :: Num a => Bool -> a
191 bool2double :: Bool -> Double
192 bool2double = bool2num
194 bool2int :: Bool -> Int
196 ------------------------------------------------------------------------
198 -- Normalizing && scaling data
199 scale :: [Double] -> [Double]
202 scaleMinMax :: [Double] -> [Double]
203 scaleMinMax xs = map (\x -> (x - mi / (ma - mi + 1) )) xs'
209 scaleNormalize :: [Double] -> [Double]
210 scaleNormalize xs = map (\x -> (x - v / (m + 1))) xs'
216 normalize :: [Double] -> [Double]
217 normalize as = normalizeWith identity as
219 normalizeWith :: Fractional b => (a -> b) -> [a] -> [b]
220 normalizeWith extract bs = map (\x -> x/(sum bs')) bs'
224 -- Zip functions to add
225 zipFst :: ([b] -> [a]) -> [b] -> [(a, b)]
226 zipFst f xs = zip (f xs) xs
228 zipSnd :: ([a] -> [b]) -> [a] -> [(a, b)]
229 zipSnd f xs = zip xs (f xs)
232 maximumWith :: (Ord a1, Foldable t) => (a2 -> a1) -> t a2 -> a2
233 maximumWith f = L.maximumBy (compare `on` f)
235 -- | To get all combinations of a list with no
236 -- repetition and apply a function to the resulting list of pairs
237 listToCombi :: forall a b. (a -> b) -> [a] -> [(b,b)]
238 listToCombi f l = [ (f x, f y) | (x:rest) <- L.tails l, y <- rest ]
240 ------------------------------------------------------------------------
241 -- Empty List Sugar Error Handling
242 -- TODO add Garg Monad Errors
244 listSafe1 :: Text -> ([a] -> Maybe a)
246 listSafe1 s f e xs = maybe (panic $ h <> e) identity (f xs)
248 h = "[ERR][Gargantext] Empty list for " <> s <> " in "
250 head' :: Text -> [a] -> a
251 head' = listSafe1 "head" headMay
253 last' :: Text -> [a] -> a
254 last' = listSafe1 "last" lastMay
256 ------------------------------------------------------------------------
258 listSafeN :: Text -> ([a] -> Maybe [a])
259 -> Text -> [a] -> [a]
260 listSafeN s f e xs = maybe (panic $ h <> e) identity (f xs)
262 h = "[ERR][Gargantext] Empty list for " <> s <> " in "
264 tail' :: Text -> [a] -> [a]
265 tail' = listSafeN "tail" tailMay
267 init' :: Text -> [a] -> [a]
268 init' = listSafeN "init" initMay
270 ------------------------------------------------------------------------
271 --- Some Statistics sugar functions
272 -- Exponential Average
273 eavg :: [Double] -> Double
274 eavg (x:xs) = a*x + (1-a)*(eavg xs)
279 mean :: Fractional a => [a] -> a
280 mean xs = sum xs / fromIntegral (length xs)
282 sumMaybe :: Num a => [Maybe a] -> Maybe a
283 sumMaybe = fmap sum . M.sequence
285 variance :: Floating a => [a] -> a
286 variance xs = sum ys / (fromIntegral (length xs) - 1)
289 ys = map (\x -> (x - m) ** 2) xs
291 deviation :: Floating a => [a] -> a
292 deviation = sqrt . variance
294 movingAverage :: (Eq b, Fractional b) => Int -> [b] -> [b]
295 movingAverage steps xs = map mean $ chunkAlong steps 1 xs
297 ma :: [Double] -> [Double]
301 -----------------------------------------------------------------------
305 fib n = fib (n-1) + fib (n-2)
309 -----------------------------------------------------------------------
310 -- Memory Optimization
312 inMVarIO :: MonadIO m => m b -> m b
314 mVar <- liftIO newEmptyMVar
316 _ <- liftIO $ forkIO $ putMVar mVar zVar
317 liftIO $ takeMVar mVar
323 _ <- liftIO $ forkIO $ putMVar mVar zVar
324 liftIO $ takeMVar mVar