{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE TypeFamilies #-}
module HaskellWorks.Data.Filter
( Container(..)
, Filter(..)
) where
import Data.Int
import Data.Word
import HaskellWorks.Data.Container
import qualified Data.ByteString as BS
import qualified Data.List as L
import qualified Data.Vector as DV
import qualified Data.Vector.Storable as DVS
class Container v => Filter v where
filter :: (Elem v -> Bool) -> v -> v
instance Filter String where
filter :: (Elem String -> Bool) -> String -> String
filter = (Elem String -> Bool) -> String -> String
forall a. (a -> Bool) -> [a] -> [a]
L.filter
{-# INLINE filter #-}
instance Filter BS.ByteString where
filter :: (Elem ByteString -> Bool) -> ByteString -> ByteString
filter = (Word8 -> Bool) -> ByteString -> ByteString
(Elem ByteString -> Bool) -> ByteString -> ByteString
BS.filter
{-# INLINE filter #-}
instance Filter (DV.Vector Word8) where
filter :: (Elem (Vector Word8) -> Bool) -> Vector Word8 -> Vector Word8
filter = (Elem (Vector Word8) -> Bool) -> Vector Word8 -> Vector Word8
forall a. (a -> Bool) -> Vector a -> Vector a
DV.filter
{-# INLINE filter #-}
instance Filter (DV.Vector Word16) where
filter :: (Elem (Vector Word16) -> Bool) -> Vector Word16 -> Vector Word16
filter = (Elem (Vector Word16) -> Bool) -> Vector Word16 -> Vector Word16
forall a. (a -> Bool) -> Vector a -> Vector a
DV.filter
{-# INLINE filter #-}
instance Filter (DV.Vector Word32) where
filter :: (Elem (Vector Word32) -> Bool) -> Vector Word32 -> Vector Word32
filter = (Elem (Vector Word32) -> Bool) -> Vector Word32 -> Vector Word32
forall a. (a -> Bool) -> Vector a -> Vector a
DV.filter
{-# INLINE filter #-}
instance Filter (DV.Vector Word64) where
filter :: (Elem (Vector Word64) -> Bool) -> Vector Word64 -> Vector Word64
filter = (Elem (Vector Word64) -> Bool) -> Vector Word64 -> Vector Word64
forall a. (a -> Bool) -> Vector a -> Vector a
DV.filter
{-# INLINE filter #-}
instance Filter (DVS.Vector Word8) where
filter :: (Elem (Vector Word8) -> Bool) -> Vector Word8 -> Vector Word8
filter = (Elem (Vector Word8) -> Bool) -> Vector Word8 -> Vector Word8
forall a. Storable a => (a -> Bool) -> Vector a -> Vector a
DVS.filter
{-# INLINE filter #-}
instance Filter (DVS.Vector Word16) where
filter :: (Elem (Vector Word16) -> Bool) -> Vector Word16 -> Vector Word16
filter = (Elem (Vector Word16) -> Bool) -> Vector Word16 -> Vector Word16
forall a. Storable a => (a -> Bool) -> Vector a -> Vector a
DVS.filter
{-# INLINE filter #-}
instance Filter (DVS.Vector Word32) where
filter :: (Elem (Vector Word32) -> Bool) -> Vector Word32 -> Vector Word32
filter = (Elem (Vector Word32) -> Bool) -> Vector Word32 -> Vector Word32
forall a. Storable a => (a -> Bool) -> Vector a -> Vector a
DVS.filter
{-# INLINE filter #-}
instance Filter (DVS.Vector Word64) where
filter :: (Elem (Vector Word64) -> Bool) -> Vector Word64 -> Vector Word64
filter = (Elem (Vector Word64) -> Bool) -> Vector Word64 -> Vector Word64
forall a. Storable a => (a -> Bool) -> Vector a -> Vector a
DVS.filter
{-# INLINE filter #-}
instance Filter (DV.Vector Int8) where
filter :: (Elem (Vector Int8) -> Bool) -> Vector Int8 -> Vector Int8
filter = (Elem (Vector Int8) -> Bool) -> Vector Int8 -> Vector Int8
forall a. (a -> Bool) -> Vector a -> Vector a
DV.filter
{-# INLINE filter #-}
instance Filter (DV.Vector Int16) where
filter :: (Elem (Vector Int16) -> Bool) -> Vector Int16 -> Vector Int16
filter = (Elem (Vector Int16) -> Bool) -> Vector Int16 -> Vector Int16
forall a. (a -> Bool) -> Vector a -> Vector a
DV.filter
{-# INLINE filter #-}
instance Filter (DV.Vector Int32) where
filter :: (Elem (Vector Int32) -> Bool) -> Vector Int32 -> Vector Int32
filter = (Elem (Vector Int32) -> Bool) -> Vector Int32 -> Vector Int32
forall a. (a -> Bool) -> Vector a -> Vector a
DV.filter
{-# INLINE filter #-}
instance Filter (DV.Vector Int64) where
filter :: (Elem (Vector Int64) -> Bool) -> Vector Int64 -> Vector Int64
filter = (Elem (Vector Int64) -> Bool) -> Vector Int64 -> Vector Int64
forall a. (a -> Bool) -> Vector a -> Vector a
DV.filter
{-# INLINE filter #-}
instance Filter (DVS.Vector Int8) where
filter :: (Elem (Vector Int8) -> Bool) -> Vector Int8 -> Vector Int8
filter = (Elem (Vector Int8) -> Bool) -> Vector Int8 -> Vector Int8
forall a. Storable a => (a -> Bool) -> Vector a -> Vector a
DVS.filter
{-# INLINE filter #-}
instance Filter (DVS.Vector Int16) where
filter :: (Elem (Vector Int16) -> Bool) -> Vector Int16 -> Vector Int16
filter = (Elem (Vector Int16) -> Bool) -> Vector Int16 -> Vector Int16
forall a. Storable a => (a -> Bool) -> Vector a -> Vector a
DVS.filter
{-# INLINE filter #-}
instance Filter (DVS.Vector Int32) where
filter :: (Elem (Vector Int32) -> Bool) -> Vector Int32 -> Vector Int32
filter = (Elem (Vector Int32) -> Bool) -> Vector Int32 -> Vector Int32
forall a. Storable a => (a -> Bool) -> Vector a -> Vector a
DVS.filter
{-# INLINE filter #-}
instance Filter (DVS.Vector Int64) where
filter :: (Elem (Vector Int64) -> Bool) -> Vector Int64 -> Vector Int64
filter = (Elem (Vector Int64) -> Bool) -> Vector Int64 -> Vector Int64
forall a. Storable a => (a -> Bool) -> Vector a -> Vector a
DVS.filter
{-# INLINE filter #-}
instance Filter (DVS.Vector Int) where
filter :: (Elem (Vector Int) -> Bool) -> Vector Int -> Vector Int
filter = (Elem (Vector Int) -> Bool) -> Vector Int -> Vector Int
forall a. Storable a => (a -> Bool) -> Vector a -> Vector a
DVS.filter
{-# INLINE filter #-}