classy-prelude-0.5.7: A typeclass-based Prelude.

Safe HaskellNone

ClassyPrelude.Classes

Synopsis

Documentation

class CanMap ci co i o | ci -> i, co -> o, ci o -> co, co i -> ci where

Methods

map :: (i -> o) -> ci -> co

Instances

CanMap LText LText Char Char 
CanMap LByteString LByteString Word8 Word8 
CanMap Text Text Char Char 
CanMap ByteString ByteString Word8 Word8 
CanMap [a] [b] a b 
CanMap (Maybe a) (Maybe b) a b 
CanMap (Vector a) (Vector b) a b 
(Eq b, Hashable b) => CanMap (HashSet a) (HashSet b) a b 
(Ord a, Ord b) => CanMap (Set a) (Set b) a b 
CanMap (Seq a) (Seq b) a b 
CanMap (HashMap k v1) (HashMap k v2) v1 v2 
CanMap (Map k v1) (Map k v2) v1 v2 

class CanConcatMap ci co i o | ci -> i, co -> o, ci o -> co, co i -> ci where

Methods

concatMap :: (i -> o) -> ci -> co

class CanFilter c i | c -> i where

Methods

filter :: (i -> Bool) -> c -> c

class CanFilterM c i | c -> i where

Methods

filterM :: Monad m => (i -> m Bool) -> c -> m c

Instances

CanFilterM [a] a 
CanFilterM (Vector a) a 
CanFilterM (Seq a) a 

class CanSingleton c i | c -> i where

Methods

singleton :: i -> c

class CanNull c where

Methods

null :: c -> Bool

class CanPack c i | c -> i where

Methods

pack :: [i] -> c

unpack :: c -> [i]

subsequences :: c -> [c]

permutations :: c -> [c]

Instances

CanPack LText Char 
CanPack LByteString Word8 
CanPack FilePath Char 
CanPack Text Char 
CanPack ByteString Word8 
CanPack [a] a 
CanPack (Maybe a) a 
CanPack (Vector a) a 
(Hashable x, Eq x) => CanPack (HashSet x) x 
Ord x => CanPack (Set x) x 
CanPack (Seq a) a 
(Eq k, Hashable k) => CanPack (HashMap k v) (k, v) 
Ord k => CanPack (Map k v) (k, v) 

class Monad m => CanMapM ci mco m i o | ci -> i, mco -> m o, ci o m -> mco, mco i -> ci where

Methods

mapM :: (i -> m o) -> ci -> mco

Instances

Monad m => CanMapM [i] (m [o]) m i o 
Monad m => CanMapM (Maybe i) (m (Maybe o)) m i o 
Monad m => CanMapM (Vector i) (m (Vector o)) m i o 
Monad m => CanMapM (Seq i) (m (Seq o)) m i o 

class CanMapM_ ci i | ci -> i where

Methods

mapM_ :: Monad m => (i -> m o) -> ci -> m ()

Instances

CanMapM_ [a] a 
CanMapM_ (Maybe a) a 
CanMapM_ (Vector a) a 
(Eq a, Hashable a) => CanMapM_ (HashSet a) a 
Ord a => CanMapM_ (Set a) a 
CanMapM_ (Seq a) a 

class CanReplicateM c i len | c -> i len where

Methods

replicateM :: Monad m => len -> m i -> m c

Instances

class CanReplicateM_ i len where

Methods

replicateM_ :: Monad m => len -> m i -> m ()

Instances

class CanLookup c k v | c -> k v where

Methods

lookup :: k -> c -> Maybe v

Instances

Eq k => CanLookup [(k, v)] k v 
(Eq k, Hashable k) => CanLookup (HashMap k v) k v 
Ord k => CanLookup (Map k v) k v 

class CanInsert f where

Methods

insert :: f

Instances

(CanInsertVal c' k v, ~ * c c') => CanInsert (k -> v -> c -> c') 
(Eq x, Hashable x, ~ * (HashSet x) s, ~ * x x') => CanInsert (x' -> s -> HashSet x) 
(Ord x, ~ * (Set x) s, ~ * x x') => CanInsert (x' -> s -> Set x) 

class CanInsertVal c k v | c -> k v where

Methods

insertVal :: k -> v -> c -> c

Instances

Eq k => CanInsertVal [(k, v)] k v 
(Eq k, Hashable k) => CanInsertVal (HashMap k v) k v 
Ord k => CanInsertVal (Map k v) k v 

class CanDelete f where

Methods

delete :: f

Instances

(CanDeleteVal c' k, ~ * c c') => CanDelete (k -> c -> c') 

class CanDeleteVal c k | c -> k where

Methods

deleteVal :: k -> c -> c

Instances

Eq k => CanDeleteVal [(k, v)] k 
Ord x => CanDeleteVal (Set x) x 
(Eq k, Hashable k) => CanDeleteVal (HashMap k v) k 
Ord k => CanDeleteVal (Map k v) k 

class CanMember c k | c -> k where

Methods

member :: k -> c -> Bool

notMember :: k -> c -> Bool

Instances

Eq x => CanMember [x] x 
Eq x => CanMember (Maybe x) x 
Eq x => CanMember (Vector x) x 
(Eq x, Hashable x) => CanMember (HashSet x) x 
Ord x => CanMember (Set x) x 
Eq x => CanMember (Seq x) x 

class CanReadFile a where

Methods

readFile :: MonadIO m => FilePath -> m a

class CanWriteFile a where

Methods

writeFile :: MonadIO m => FilePath -> a -> m ()

class CanBreak c i | c -> i where

Methods

break :: (i -> Bool) -> c -> (c, c)

span :: (i -> Bool) -> c -> (c, c)

dropWhile :: (i -> Bool) -> c -> c

takeWhile :: (i -> Bool) -> c -> c

class CanAny c i | c -> i where

Methods

any :: (i -> Bool) -> c -> Bool

all :: (i -> Bool) -> c -> Bool

class CanFold c i accum | c -> i where

Methods

fold :: (accum -> i -> accum) -> accum -> c -> accum

Strict left fold.

Instances

CanFold LText Char accum 
CanFold LByteString Word8 accum 
CanFold Text Char accum 
CanFold ByteString Word8 accum 
CanFold [a] a accum 
CanFold (Maybe a) a accum 
CanFold (Vector a) a accum 
CanFold (HashSet a) a accum 
CanFold (Set a) a accum 
CanFold (Seq a) a accum 

class CanWords t where

Methods

words :: t -> [t]

unwords :: [t] -> t

Instances

class CanLines t where

Methods

lines :: t -> [t]

Instances

class CanUnlines t where

Methods

unlines :: [t] -> t

Instances

class CanSplit c i | c -> i where

Methods

split :: (i -> Bool) -> c -> [c]

class CanIsInfixOf a where

Methods

isInfixOf :: a -> a -> Bool

class CanToChunks c i | c -> i, i -> c where

Methods

toChunks :: c -> [i]

fromChunks :: [i] -> c

class CanEncodeUtf8 ci co | co -> ci, ci -> co where

Methods

encodeUtf8 :: ci -> co

class CanDecodeUtf8 ci co | co -> ci, ci -> co where

Note: implementations should ensure that decodeUtf8 is a total function. As such, the standard decodeUtf8 provided by the text package should not be used, but instead decodeUtf8With lenientDecode.

Methods

decodeUtf8 :: ci -> co

class CanToStrict a b where

Methods

toStrict :: a -> b

fromStrict :: b -> a

class CanGetLine a where

Methods

getLine :: a

Instances

class CanToLower a where

Methods

toLower :: a -> a

class CanToUpper a where

Methods

toUpper :: a -> a

class CanToCaseFold a where

Methods

toCaseFold :: a -> a

class CanFind c i | c -> i where

Methods

find :: (i -> Bool) -> c -> Maybe i

Instances

CanFind LText Char 
CanFind Text Char 
CanFind [a] a 
CanFind (Maybe a) a 
CanFind (Vector a) a 
CanFind (Set a) a 
CanFind (Seq a) a 
CanFind (HashMap k v) v 
CanFind (Map k v) v 

class CanConcat c i | c -> i where

Methods

concat :: c -> i

Instances

Monoid m => CanConcat [m] m 
Monoid m => CanConcat (Vector m) m 
Monoid m => CanConcat (Set m) m 
Monoid m => CanConcat (Seq m) m 
Monoid v => CanConcat (HashMap k v) v 
Monoid v => CanConcat (Map k v) v 

class CanPartition c i | c -> i where

Methods

partition :: (i -> Bool) -> c -> (c, c)

class CanNubBy c i | c -> i where

Methods

nubBy :: (i -> i -> Bool) -> c -> c

nub :: (Ord i, CanNubBy c i) => c -> c

Instances

CanNubBy [a] a 

class CanUnion c where

Methods

union :: c -> c -> c

Instances

Eq a => CanUnion [a] 
(Eq a, Hashable a) => CanUnion (HashSet a) 
Ord a => CanUnion (Set a) 
(Hashable k, Eq k) => CanUnion (HashMap k a) 
Ord k => CanUnion (Map k a) 

class CanDifference c where

Methods

difference :: c -> c -> c

Instances

Eq a => CanDifference [a] 
(Eq a, Hashable a) => CanDifference (HashSet a) 
Ord a => CanDifference (Set a) 
(Hashable k, Eq k) => CanDifference (HashMap k a) 
Ord k => CanDifference (Map k a) 

class CanIntersection c where

Methods

intersection :: c -> c -> c

Instances

class CanSortBy c a | c -> a where

Methods

sortBy :: (a -> a -> Ordering) -> c -> c

Instances

CanSortBy [a] a 
CanSortBy (Seq a) a 

class Ord a => CanSort c a | c -> a where

Methods

sort :: c -> c

Instances

Ord a => CanSort [a] a 
Ord a => CanSort (Seq a) a 

class CanCons c a where

Methods

cons :: a -> c -> c

class CanCompareLength c where

Methods

compareLength :: Integral l => c -> l -> Ordering

This is a more effective alternative to statements like i >= length xs for types having an O(n) complexity of length operation like list or Text. It does not traverse the whole data structure if the value being compared to is lesser.

class CanGroupBy c a | c -> a where

Methods

groupBy :: (a -> a -> Bool) -> c -> [c]

class CanGroup c a | c -> a where

Methods

group :: c -> [c]

class CanRepeat c a | c -> a where

Methods

repeat :: a -> c

class CanZipWith c1 i1 c2 i2 c3 i3 | c1 -> i1, c2 -> i2, c3 -> i3 where

Methods

zipWith :: (i1 -> i2 -> i3) -> c1 -> c2 -> c3

class CanZipWith3 c1 i1 c2 i2 c3 i3 c4 i4 | c1 -> i1, c2 -> i2, c3 -> i3, c4 -> i4 where

Methods

zipWith3 :: (i1 -> i2 -> i3 -> i4) -> c1 -> c2 -> c3 -> c4

Instances

CanZipWith3 [a] a [b] b [c] c [d] d 
CanZipWith3 (Vector a) a (Vector b) b (Vector c) c (Vector d) d 
CanZipWith3 (Seq a) a (Seq b) b (Seq c) c (Seq d) d 

class CanZipWith4 c1 i1 c2 i2 c3 i3 c4 i4 c5 i5 | c1 -> i1, c2 -> i2, c3 -> i3, c4 -> i4, c5 -> i5 where

Methods

zipWith4 :: (i1 -> i2 -> i3 -> i4 -> i5) -> c1 -> c2 -> c3 -> c4 -> c5

Instances

CanZipWith4 [a] a [b] b [c] c [d] d [e] e 
CanZipWith4 (Vector a) a (Vector b) b (Vector c) c (Vector d) d (Vector e) e 
CanZipWith4 (Seq a) a (Seq b) b (Seq c) c (Seq d) d (Seq e) e 

class CanZipWith5 c1 i1 c2 i2 c3 i3 c4 i4 c5 i5 c6 i6 | c1 -> i1, c2 -> i2, c3 -> i3, c4 -> i4, c5 -> i5, c6 -> i6 where

Methods

zipWith5 :: (i1 -> i2 -> i3 -> i4 -> i5 -> i6) -> c1 -> c2 -> c3 -> c4 -> c5 -> c6

Instances

CanZipWith5 [a] a [b] b [c] c [d] d [e] e [f] f 
CanZipWith5 (Vector a) a (Vector b) b (Vector c) c (Vector d) d (Vector e) e (Vector f) f 

class CanZipWith6 c1 i1 c2 i2 c3 i3 c4 i4 c5 i5 c6 i6 c7 i7 | c1 -> i1, c2 -> i2, c3 -> i3, c4 -> i4, c5 -> i5, c6 -> i6, c7 -> i7 where

Methods

zipWith6 :: (i1 -> i2 -> i3 -> i4 -> i5 -> i6 -> i7) -> c1 -> c2 -> c3 -> c4 -> c5 -> c6 -> c7

Instances

CanZipWith6 [a] a [b] b [c] c [d] d [e] e [f] f [g] g 
CanZipWith6 (Vector a) a (Vector b) b (Vector c) c (Vector d) d (Vector e) e (Vector f) f (Vector g) g 

class CanZipWith7 c1 i1 c2 i2 c3 i3 c4 i4 c5 i5 c6 i6 c7 i7 c8 i8 | c1 -> i1, c2 -> i2, c3 -> i3, c4 -> i4, c5 -> i5, c6 -> i6, c7 -> i7, c8 -> i8 where

Methods

zipWith7 :: (i1 -> i2 -> i3 -> i4 -> i5 -> i6 -> i7 -> i8) -> c1 -> c2 -> c3 -> c4 -> c5 -> c6 -> c7 -> c8

Instances

CanZipWith7 [a] a [b] b [c] c [d] d [e] e [f] f [g] g [h] h 

class CanZip c1 i1 c2 i2 t | c1 -> i1, c2 -> i2 where

Methods

zip :: c1 -> c2 -> t (i1, i2)

class CanZip3 c1 i1 c2 i2 c3 i3 t | c1 -> i1, c2 -> i2, c3 -> i3 where

Methods

zip3 :: c1 -> c2 -> c3 -> t (i1, i2, i3)

Instances

CanZip3 [a] a [b] b [c] c [] 
CanZip3 (Vector a) a (Vector b) b (Vector c) c Vector 
CanZip3 (Seq a) a (Seq b) b (Seq c) c Seq 

class CanZip4 c1 i1 c2 i2 c3 i3 c4 i4 t | c1 -> i1, c2 -> i2, c3 -> i3, c4 -> i4 where

Methods

zip4 :: c1 -> c2 -> c3 -> c4 -> t (i1, i2, i3, i4)

Instances

CanZip4 [a] a [b] b [c] c [d] d [] 
CanZip4 (Vector a) a (Vector b) b (Vector c) c (Vector d) d Vector 
CanZip4 (Seq a) a (Seq b) b (Seq c) c (Seq d) d Seq 

class CanZip5 c1 i1 c2 i2 c3 i3 c4 i4 c5 i5 t | c1 -> i1, c2 -> i2, c3 -> i3, c4 -> i4, c5 -> i5 where

Methods

zip5 :: c1 -> c2 -> c3 -> c4 -> c5 -> t (i1, i2, i3, i4, i5)

Instances

CanZip5 [a] a [b] b [c] c [d] d [e] e [] 
CanZip5 (Vector a) a (Vector b) b (Vector c) c (Vector d) d (Vector e) e Vector 

class CanZip6 c1 i1 c2 i2 c3 i3 c4 i4 c5 i5 c6 i6 t | c1 -> i1, c2 -> i2, c3 -> i3, c4 -> i4, c5 -> i5, c6 -> i6 where

Methods

zip6 :: c1 -> c2 -> c3 -> c4 -> c5 -> c6 -> t (i1, i2, i3, i4, i5, i6)

Instances

CanZip6 [a] a [b] b [c] c [d] d [e] e [f] f [] 
CanZip6 (Vector a) a (Vector b) b (Vector c) c (Vector d) d (Vector e) e (Vector f) f Vector 

class CanZip7 c1 i1 c2 i2 c3 i3 c4 i4 c5 i5 c6 i6 c7 i7 t | c1 -> i1, c2 -> i2, c3 -> i3, c4 -> i4, c5 -> i5, c6 -> i6, c7 -> i7 where

Methods

zip7 :: c1 -> c2 -> c3 -> c4 -> c5 -> c6 -> c7 -> t (i1, i2, i3, i4, i5, i6, i7)

Instances

CanZip7 [a] a [b] b [c] c [d] d [e] e [f] f [g] g [] 

class CanUnzip c1 i1 c2 i2 t | c1 -> i1, c2 -> i2 where

Methods

unzip :: t (i1, i2) -> (c1, c2)

class CanUnzip3 c1 i1 c2 i2 c3 i3 t | c1 -> i1, c2 -> i2, c3 -> i3 where

Methods

unzip3 :: t (i1, i2, i3) -> (c1, c2, c3)

Instances

CanUnzip3 [a] a [b] b [c] c [] 
CanUnzip3 (Vector a) a (Vector b) b (Vector c) c Vector 

class CanUnzip4 c1 i1 c2 i2 c3 i3 c4 i4 t | c1 -> i1, c2 -> i2, c3 -> i3, c4 -> i4 where

Methods

unzip4 :: t (i1, i2, i3, i4) -> (c1, c2, c3, c4)

Instances

CanUnzip4 [a] a [b] b [c] c [d] d [] 
CanUnzip4 (Vector a) a (Vector b) b (Vector c) c (Vector d) d Vector 

class CanUnzip5 c1 i1 c2 i2 c3 i3 c4 i4 c5 i5 t | c1 -> i1, c2 -> i2, c3 -> i3, c4 -> i4, c5 -> i5 where

Methods

unzip5 :: t (i1, i2, i3, i4, i5) -> (c1, c2, c3, c4, c5)

Instances

CanUnzip5 [a] a [b] b [c] c [d] d [e] e [] 
CanUnzip5 (Vector a) a (Vector b) b (Vector c) c (Vector d) d (Vector e) e Vector 

class CanUnzip6 c1 i1 c2 i2 c3 i3 c4 i4 c5 i5 c6 i6 t | c1 -> i1, c2 -> i2, c3 -> i3, c4 -> i4, c5 -> i5, c6 -> i6 where

Methods

unzip6 :: t (i1, i2, i3, i4, i5, i6) -> (c1, c2, c3, c4, c5, c6)

Instances

CanUnzip6 [a] a [b] b [c] c [d] d [e] e [f] f [] 
CanUnzip6 (Vector a) a (Vector b) b (Vector c) c (Vector d) d (Vector e) e (Vector f) f Vector 

class CanUnzip7 c1 i1 c2 i2 c3 i3 c4 i4 c5 i5 c6 i6 c7 i7 t | c1 -> i1, c2 -> i2, c3 -> i3, c4 -> i4, c5 -> i5, c6 -> i6, c7 -> i7 where

Methods

unzip7 :: t (i1, i2, i3, i4, i5, i6, i7) -> (c1, c2, c3, c4, c5, c6, c7)

Instances

CanUnzip7 [a] a [b] b [c] c [d] d [e] e [f] f [g] g [] 

class CanEmpty a where

Methods

empty :: a