classy-prelude-0.5.1: 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 whereSource

Methods

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

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 (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 whereSource

Methods

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

class CanFilter c i | c -> i whereSource

Methods

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

class CanFilterM c i | c -> i whereSource

Methods

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

Instances

class CanSingleton c i | c -> i whereSource

Methods

singleton :: i -> cSource

class CanPack c i | c -> i whereSource

Methods

pack :: [i] -> cSource

unpack :: c -> [i]Source

subsequences :: c -> [c]Source

permutations :: c -> [c]Source

Instances

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

Methods

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

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 

class CanMapM_ ci i | ci -> i whereSource

Methods

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

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 

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

Methods

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

Instances

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

Methods

lookup :: k -> c -> Maybe vSource

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 whereSource

Methods

insert :: fSource

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 whereSource

Methods

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

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 whereSource

Methods

delete :: fSource

Instances

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

class CanDeleteVal c k | c -> k whereSource

Methods

deleteVal :: k -> c -> cSource

Instances

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

class CanMember c k | c -> k whereSource

Methods

member :: k -> c -> BoolSource

notMember :: k -> c -> BoolSource

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 

class CanBreak c i | c -> i whereSource

Methods

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

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

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

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

class CanAny c i | c -> i whereSource

Methods

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

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

class CanFold c i accum | c -> i whereSource

Methods

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

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 

class CanWords t whereSource

Methods

words :: t -> [t]Source

unwords :: [t] -> tSource

Instances

class CanLines t whereSource

Methods

lines :: t -> [t]Source

Instances

class CanUnlines t whereSource

Methods

unlines :: [t] -> tSource

Instances

class CanSplit c i | c -> i whereSource

Methods

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

class CanIsInfixOf a whereSource

Methods

isInfixOf :: a -> a -> BoolSource

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

Methods

toChunks :: c -> [i]Source

fromChunks :: [i] -> cSource

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

Methods

encodeUtf8 :: ci -> coSource

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

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 -> coSource

class CanGetLine a whereSource

Methods

getLine :: aSource

Instances

class CanToLower a whereSource

Methods

toLower :: a -> aSource

class CanToUpper a whereSource

Methods

toUpper :: a -> aSource

class CanFind c i | c -> i whereSource

Methods

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

Instances

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

class CanConcat c i | c -> i whereSource

Methods

concat :: c -> iSource

Instances

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

class CanNubBy c i | c -> i whereSource

Methods

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

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

Instances

CanNubBy [a] a 

class CanUnion c whereSource

Methods

union :: c -> c -> cSource

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 whereSource

Methods

difference :: c -> c -> cSource

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 whereSource

Methods

intersection :: c -> c -> cSource

Instances

class CanSortBy c a whereSource

Methods

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

sort :: c a -> c aSource

Instances

Ord a => CanSortBy [] a 

class CanCons c a whereSource

Methods

cons :: a -> c -> cSource

class CanCompareLength c whereSource

Methods

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

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.