[FIX] dep with cabal file
[gargantext.git] / src / Gargantext / Prelude.hs
index c6b3d81907afc89c4565384ad8be2ddccb860942..80532b6f38a9afd4ab8a7bad44e17961d89c1391 100644 (file)
@@ -7,16 +7,11 @@ Maintainer  : team@gargantext.org
 Stability   : experimental
 Portability : POSIX
 
-Here is a longer description of this module, containing some
-commentary with @some markup@.
 -}
 
-{-# OPTIONS_GHC -fno-warn-name-shadowing #-}
-{-# OPTIONS_GHC -fno-warn-type-defaults  #-}
 
-{-# LANGUAGE     NoImplicitPrelude       #-}
-{-# LANGUAGE     OverloadedStrings       #-}
-{-# LANGUAGE     RankNTypes              #-}
+{-# OPTIONS_GHC -fno-warn-orphans        #-}
+{-# OPTIONS_GHC -fno-warn-type-defaults  #-}
 
 module Gargantext.Prelude
   ( module Gargantext.Prelude
@@ -30,21 +25,26 @@ module Gargantext.Prelude
   , round
   , sortWith
   , module Prelude
+  , MonadBase(..)
+  , Typeable
   )
   where
 
+import Control.Monad.Base (MonadBase(..))
 import GHC.Exts (sortWith)
 import GHC.Err.Located (undefined)
 import GHC.Real (round)
-import Control.Monad.IO.Class (MonadIO)
+import Data.Map (Map, lookup)
 import Data.Maybe (isJust, fromJust, maybe)
+import Data.Monoid (Monoid, mempty)
+import Data.Semigroup (Semigroup, (<>))
 import Data.Text (Text)
+import Data.Typeable (Typeable)
 import Protolude ( Bool(True, False), Int, Int64, Double, Integer
                  , Fractional, Num, Maybe(Just,Nothing)
                  , Enum, Bounded, Float
                  , Floating, Char, IO
-                 , pure, (>>=), (=<<), (<*>), (<$>)
-                 , putStrLn
+                 , pure, (>>=), (=<<), (<*>), (<$>), (<&>), (>>)
                  , head, flip
                  , Ord, Integral, Foldable, RealFrac, Monad, filter
                  , reverse, map, mapM, zip, drop, take, zipWith
@@ -54,6 +54,7 @@ import Protolude ( Bool(True, False), Int, Int64, Double, Integer
                  , (+), (*), (/), (-), (.), ($), (&), (**), (^), (<), (>), log
                  , Eq, (==), (>=), (<=), (<>), (/=)
                  , (&&), (||), not, any, all
+                 , concatMap
                  , fst, snd, toS
                  , elem, die, mod, div, const, either
                  , curry, uncurry, repeat
@@ -62,18 +63,16 @@ import Protolude ( Bool(True, False), Int, Int64, Double, Integer
                  , compare
                  , on
                  , panic
+                 , seq
                  )
 
-import Prelude (Enum, Bounded, minBound, maxBound)
+import Prelude (Enum, Bounded, minBound, maxBound, putStrLn)
 -- TODO import functions optimized in Utils.Count
 -- import Protolude hiding (head, last, all, any, sum, product, length)
 -- import Gargantext.Utils.Count
 import qualified Data.List     as L hiding (head, sum)
 import qualified Control.Monad as M
-
-import Data.Map (Map)
-import qualified Data.Map as M
-
+import qualified Data.Map      as M
 import Data.Map.Strict (insertWith)
 import qualified Data.Vector as V
 import Safe (headMay, lastMay, initMay, tailMay)
@@ -82,46 +81,11 @@ import Text.Read (Read())
 import Data.String.Conversions (cs)
 
 
-printDebug :: (Show a, MonadIO m) => [Char] -> a -> m ()
-printDebug msg x = putStrLn $ msg <> " " <> show x
+printDebug :: (Show a, MonadBase IO m) => [Char] -> a -> m ()
+printDebug msg x = liftBase . putStrLn $ msg <> " " <> show x
 -- printDebug _ _ = pure ()
 
 
-map2 :: (t -> b) -> [[t]] -> [[b]]
-map2 fun = map (map fun)
-
-
--- Some Statistics sugar functions
--- Exponential Average
-eavg :: [Double] -> Double
-eavg (x:xs) = a*x + (1-a)*(eavg xs)
-  where a = 0.70
-eavg [] = 0
-
--- Simple Average
-mean :: Fractional a => [a] -> a
-mean xs = sum xs / fromIntegral (length xs)
-
-
-sumMaybe :: Num a => [Maybe a] -> Maybe a
-sumMaybe = fmap sum . M.sequence
-
-variance :: Floating a => [a] -> a
-variance xs = sum ys  / (fromIntegral (length xs) - 1)
-  where
-    m = mean xs
-    ys = map (\x -> (x - m) ** 2) xs
-
-
-deviation :: Floating a => [a] -> a
-deviation = sqrt . variance
-
-movingAverage :: (Eq b, Fractional b) => Int -> [b] -> [b]
-movingAverage steps xs = map mean $ chunkAlong steps 1 xs
-
-ma :: [Double] -> [Double]
-ma = movingAverage 3
-
 -- | splitEvery n == chunkAlong n n
 splitEvery :: Int -> [a] -> [[a]]
 splitEvery _ [] = []
@@ -176,7 +140,8 @@ chunkAlongV a b l = only (while  dropAlong)
 splitAlong :: [Int] -> [Char] -> [[Char]]
 splitAlong _ [] = [] -- No list? done
 splitAlong [] xs = [xs] -- No place to split at? Return the remainder
-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
+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
 
 takeWhileM :: (Monad m) => (a -> Bool) -> [m a] -> m [a]
 takeWhileM _ [] = return []
@@ -212,14 +177,12 @@ count2map xs = M.map (/ (fromIntegral (length xs))) (count2map' xs)
 count2map' :: (Ord k, Foldable t) => t k -> Map k Double
 count2map' xs = L.foldl' (\x y -> insertWith (+) y 1 x) M.empty xs
 
-
 trunc :: (RealFrac a, Integral c, Integral b) => b -> a -> c
 trunc n = truncate . (* 10^n)
 
 trunc' :: Int -> Double -> Double
 trunc' n x = fromIntegral $ truncate $ (x * 10^n)
 
-
 ------------------------------------------------------------------------
 bool2num :: Num a => Bool -> a
 bool2num True  = 1
@@ -248,7 +211,7 @@ scaleNormalize xs = map (\x -> (x - v / (m + 1))) xs'
     where
         v   = variance  xs'
         m   = mean      xs'
-        xs' = map abs xs
+        xs' = map abs   xs
 
 normalize :: [Double] -> [Double]
 normalize as = normalizeWith identity as
@@ -269,8 +232,8 @@ zipSnd f xs = zip xs (f xs)
 maximumWith :: (Ord a1, Foldable t) => (a2 -> a1) -> t a2 -> a2
 maximumWith f = L.maximumBy (compare `on` f)
 
-
--- | To get all combinations of a list with no repetition and apply a function to the resulting list of pairs
+-- | To get all combinations of a list with no
+-- repetition and apply a function to the resulting list of pairs
 listToCombi :: forall a b. (a -> b) -> [a] -> [(b,b)]
 listToCombi f l = [ (f x, f y) | (x:rest) <- L.tails l,  y <- rest ]
 
@@ -305,5 +268,72 @@ init' :: Text -> [a] -> [a]
 init' = listSafeN "init" initMay
 
 ------------------------------------------------------------------------
+--- Some Statistics sugar functions
+-- Exponential Average
+eavg :: [Double] -> Double
+eavg (x:xs) = a*x + (1-a)*(eavg xs)
+  where a = 0.70
+eavg [] = 0
+
+-- Simple Average
+mean :: Fractional a => [a] -> a
+mean xs = sum xs / fromIntegral (length xs)
+
+sumMaybe :: Num a => [Maybe a] -> Maybe a
+sumMaybe = fmap sum . M.sequence
 
+variance :: Floating a => [a] -> a
+variance xs = sum ys  / (fromIntegral (length xs) - 1)
+  where
+    m = mean xs
+    ys = map (\x -> (x - m) ** 2) xs
+
+deviation :: Floating a => [a] -> a
+deviation = sqrt . variance
+
+movingAverage :: (Eq b, Fractional b) => Int -> [b] -> [b]
+movingAverage steps xs = map mean $ chunkAlong steps 1 xs
 
+-----------------------------------------------------------------------
+-----------------------------------------------------------------------
+--- Map in Map = Map2
+-- To avoid Map (a,a) b
+type Map2 a b = Map a (Map a b)
+
+lookup2 :: Ord a
+        => a
+        -> a
+        -> Map2 a b
+        -> Maybe b
+lookup2 a b m = do
+  m' <- lookup a m
+  lookup b m'
+
+-----------------------------------------------------------------------
+foldM' :: (Monad m) => (a -> b -> m a) -> a -> [b] -> m a
+foldM' _ z [] = return z
+foldM' f z (x:xs) = do
+  z' <- f z x
+  z' `seq` foldM' f z' xs
+
+-----------------------------------------------------------------------
+-- | Instance for basic numerals
+-- See the difference between Double and (Int Or Integer)
+instance Monoid Double where
+  mempty = 1
+
+instance Semigroup Double where
+  (<>) a b = a * b
+
+-----------
+instance Monoid Int where
+  mempty = 0
+
+instance Semigroup Int where
+  (<>) a b = a + b
+----
+instance Monoid Integer where
+  mempty = 0
+
+instance Semigroup Integer where
+  (<>) a b = a + b