{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE BangPatterns #-}
{-# OPTIONS_GHC -fwarn-incomplete-patterns #-}
module Control.MapReduce.Engines
(
MapReduceFold
, MapReduceFoldM
, reduceFunction
, reduceFunctionM
, fromListWithHT
)
where
import qualified Control.MapReduce.Core as MRC
import qualified Control.Foldl as FL
import Control.Monad.ST as ST
import Data.Hashable ( Hashable )
import qualified Data.HashTable.Class as HT
type MapReduceFold y k c q x d = MRC.Unpack x y -> MRC.Assign k y c -> MRC.Reduce k c d -> FL.Fold x (q d)
type MapReduceFoldM m y k c q x d = MRC.UnpackM m x y -> MRC.AssignM m k y c -> MRC.ReduceM m k c d -> FL.FoldM m x (q d)
reduceFunction :: (Foldable h, Functor h) => MRC.Reduce k x d -> k -> h x -> d
reduceFunction :: Reduce k x d -> k -> h x -> d
reduceFunction (MRC.Reduce k -> forall (h :: * -> *). (Foldable h, Functor h) => h x -> d
f) k
k = k -> forall (h :: * -> *). (Foldable h, Functor h) => h x -> d
f k
k
reduceFunction (MRC.ReduceFold k -> Fold x d
f) k
k = Fold x d -> h x -> d
forall (f :: * -> *) a b. Foldable f => Fold a b -> f a -> b
FL.fold (k -> Fold x d
f k
k)
{-# INLINABLE reduceFunction #-}
reduceFunctionM
:: (Traversable h, Monad m) => MRC.ReduceM m k x d -> k -> h x -> m d
reduceFunctionM :: ReduceM m k x d -> k -> h x -> m d
reduceFunctionM (MRC.ReduceM k -> forall (h :: * -> *). (Foldable h, Functor h) => h x -> m d
f) k
k = k -> forall (h :: * -> *). (Foldable h, Functor h) => h x -> m d
f k
k
reduceFunctionM (MRC.ReduceFoldM k -> FoldM m x d
f) k
k = FoldM m x d -> h x -> m d
forall (f :: * -> *) (m :: * -> *) a b.
(Foldable f, Monad m) =>
FoldM m a b -> f a -> m b
FL.foldM (k -> FoldM m x d
f k
k)
{-# INLINABLE reduceFunctionM #-}
fromListWithHT
:: forall h k v s
. (HT.HashTable h, Eq k, Hashable k)
=> (v -> v -> v)
-> [(k, v)]
-> ST.ST s (h s k v)
fromListWithHT :: (v -> v -> v) -> [(k, v)] -> ST s (h s k v)
fromListWithHT v -> v -> v
f [(k, v)]
l = do
h s k v
ht <- ST s (h s k v)
forall (h :: * -> * -> * -> *) s k v. HashTable h => ST s (h s k v)
HT.new
h s k v -> [(k, v)] -> ST s (h s k v)
go h s k v
ht [(k, v)]
l
where
g :: v -> Maybe v -> (Maybe v, ())
g v
x Maybe v
mx = (v -> Maybe v
forall a. a -> Maybe a
Just (v -> Maybe v) -> v -> Maybe v
forall a b. (a -> b) -> a -> b
$ v -> (v -> v) -> Maybe v -> v
forall b a. b -> (a -> b) -> Maybe a -> b
maybe v
x (v -> v -> v
`f` v
x) Maybe v
mx, ())
go :: h s k v -> [(k, v)] -> ST s (h s k v)
go h s k v
ht = [(k, v)] -> ST s (h s k v)
go'
where
go' :: [(k, v)] -> ST s (h s k v)
go' [] = h s k v -> ST s (h s k v)
forall (m :: * -> *) a. Monad m => a -> m a
return h s k v
ht
go' ((!k
k, !v
v) : [(k, v)]
xs) = do
h s k v -> k -> (Maybe v -> (Maybe v, ())) -> ST s ()
forall (h :: * -> * -> * -> *) k s v a.
(HashTable h, Eq k, Hashable k) =>
h s k v -> k -> (Maybe v -> (Maybe v, a)) -> ST s a
HT.mutate h s k v
ht k
k (v -> Maybe v -> (Maybe v, ())
g v
v)
[(k, v)] -> ST s (h s k v)
go' [(k, v)]
xs
{-# INLINABLE fromListWithHT #-}