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

Safe HaskellNone

ClassyPrelude

Contents

Synopsis

CorePrelude

data Seq a

General-purpose finite sequences.

Instances

Monad Seq 
Functor Seq 
Typeable1 Seq 
MonadPlus Seq 
Foldable Seq 
Traversable Seq 
Eq a => Eq (Seq a) 
Data a => Data (Seq a) 
Ord a => Ord (Seq a) 
Read a => Read (Seq a) 
Show a => Show (Seq a) 
Monoid (Seq a) 
NFData a => NFData (Seq a) 
CanEmpty (Seq a) 
CanReverse (Seq a) 
Eq a => CanStripSuffix (Seq a) 
Eq a => CanStripPrefix (Seq a) 
CanNull (Seq a) 
CanUncons (Seq a) a 
CanCons (Seq a) a 
Ord a => CanSort (Seq a) a 
CanSortBy (Seq a) a 
CanPartition (Seq a) a 
Monoid m => CanConcat (Seq m) m 
CanFind (Seq a) a 
CanSplitAt (Seq a) Int 
CanAny (Seq a) a 
CanBreak (Seq a) a 
Eq x => CanMember (Seq x) x 
CanMapM_ (Seq a) a 
CanIntersperse (Seq a) a 
CanPack (Seq a) a 
CanSingleton (Seq a) a 
CanLength (Seq a) Int 
CanFilterM (Seq a) a 
CanFilter (Seq a) a 
CanReplicate (Seq a) a Int 
CanFold (Seq a) a accum 
CanReplicateM (Seq a) a Int 
CanZip (Seq a) a (Seq b) b Seq 
CanZipWith (Seq a) a (Seq b) b (Seq c) c 
CanZip3 (Seq a) a (Seq b) b (Seq c) c Seq 
CanZipWith3 (Seq a) a (Seq b) b (Seq c) c (Seq d) d 
CanZip4 (Seq a) a (Seq b) b (Seq c) c (Seq d) d Seq 
CanZipWith4 (Seq a) a (Seq b) b (Seq c) c (Seq d) d (Seq e) e 
CanMap (Seq a) (Seq b) a b 
Monad m => CanMapM (Seq i) (m (Seq o)) m i o 
CanConcatMap (Seq a) (Seq b) a (Seq b) 

undefined :: aSource

Deprecated: It is highly recommended that you either avoid partial functions or provide meaningful error messages

We define our own undefined which is marked as deprecated. This makes it useful to use during development, but let's you more easily getting notification if you accidentally ship partial code in production.

The classy prelude recommendation for when you need to really have a partial function in production is to use error with a very descriptive message so that, in case an exception is thrown, you get more information than Prelude.undefined.

Since 0.5.5

Standard

Monoid

append :: Monoid m => m -> m -> mSource

(++) :: Monoid m => m -> m -> mSource

Monad

Mutable references

Non-standard

List-like classes

map :: CanMap ci co i o => (i -> o) -> ci -> coSource

concat :: CanConcat c i => c -> iSource

concatMap :: CanConcatMap ci co i o => (i -> o) -> ci -> coSource

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

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

length :: CanLength c len => c -> lenSource

singleton :: CanSingleton c i => i -> cSource

null :: CanNull c => c -> BoolSource

pack :: CanPack c i => [i] -> cSource

unpack :: CanPack c i => c -> [i]Source

repack :: (CanPack a i, CanPack b i) => a -> bSource

Repack from one type to another, dropping to a list in the middle.

repack = pack . unpack.

fromList :: CanPack c i => [i] -> cSource

toList :: CanPack c i => c -> [i]Source

mapM :: CanMapM ci mco m i o => (i -> m o) -> ci -> mcoSource

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

forM :: CanMapM ci mco m i o => ci -> (i -> m o) -> mcoSource

forM_ :: (Monad m, CanMapM_ ci i) => ci -> (i -> m o) -> m ()Source

replicateM :: (CanReplicateM c i len, Monad m) => len -> m i -> m cSource

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

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

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

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

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

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

splitAt :: CanSplitAt c i => i -> c -> (c, c)Source

take :: CanSplitAt c i => i -> c -> cSource

drop :: CanSplitAt c i => i -> c -> cSource

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

Strict left fold.

words :: CanWords t => t -> [t]Source

unwords :: CanWords t => [t] -> tSource

lines :: CanLines t => t -> [t]Source

unlines :: CanUnlines t => [t] -> tSource

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

reverse :: CanReverse a => a -> aSource

readMay :: (Read b, CanPack a Char) => a -> Maybe bSource

replicate :: CanReplicate a i len => len -> i -> aSource

intercalate :: (CanConcat c i, CanIntersperse c i) => i -> c -> iSource

intersperse :: CanIntersperse c i => i -> c -> cSource

encodeUtf8 :: CanEncodeUtf8 ci co => ci -> coSource

decodeUtf8 :: CanDecodeUtf8 ci co => ci -> coSource

subsequences :: CanPack c i => c -> [c]Source

permutations :: CanPack c i => c -> [c]Source

partition :: CanPartition c i => (i -> Bool) -> c -> (c, c)Source

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

sort :: CanSort c a => c -> cSource

sortBy :: CanSortBy c a => (a -> a -> Ordering) -> c -> cSource

sortWith :: (CanSortBy c a, Ord b) => (a -> b) -> c -> cSource

Sort elements using the user supplied function to project something out of each element. Inspired by http://hackage.haskell.org/packages/archive/base/latest/doc/html/GHC-Exts.html#v:sortWith.

group :: CanGroup c a => c -> [c]Source

groupBy :: CanGroupBy c a => (a -> a -> Bool) -> c -> [c]Source

groupWith :: (CanGroupBy c a, Eq b) => (a -> b) -> c -> [c]Source

The groupWith function uses the user supplied function which projects an element out of every list element in order to first sort the input list and then to form groups by equality on these projected elements

Inspired by http://hackage.haskell.org/packages/archive/base/latest/doc/html/GHC-Exts.html#v:groupWith

cons :: CanCons c a => a -> c -> cSource

uncons :: CanUncons c a => c -> Maybe (a, c)Source

compareLength :: (CanCompareLength c, 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.

sum :: (Foldable t, Num a) => t a -> a

The sum function computes the sum of the numbers of a structure.

product :: (Foldable t, Num a) => t a -> a

The product function computes the product of the numbers of a structure.

repeat :: CanRepeat c a => a -> cSource

Map-like

lookup :: CanLookup c k v => k -> c -> Maybe vSource

Set-like

member :: CanMember c k => k -> c -> BoolSource

notMember :: CanMember c k => k -> c -> BoolSource

elem :: CanMember c k => k -> c -> BoolSource

An alias for member

notElem :: CanMember c k => k -> c -> BoolSource

An alias for notMember

union :: CanUnion c => c -> c -> cSource

difference :: CanDifference c => c -> c -> cSource

(\\) :: CanDifference c => c -> c -> cSource

An alias for difference.

intersect :: CanIntersection c => c -> c -> cSource

An alias for intersection.

unions :: (Foldable cc, Monoid c, CanUnion c) => cc c -> cSource

Text-like

show :: (Show a, CanPack c Char) => a -> cSource

toLower :: CanToLower a => a -> aSource

toUpper :: CanToUpper a => a -> aSource

toStrict :: CanToStrict a b => a -> bSource

fromStrict :: CanToStrict a b => b -> aSource

IO

writeFile :: (CanWriteFile a, MonadIO m) => FilePath -> a -> m ()Source

print :: (Show a, MonadIO m) => a -> m ()Source

Chunking

toChunks :: CanToChunks c i => c -> [i]Source

fromChunks :: CanToChunks c i => [i] -> cSource

Exceptions

catchAny :: MonadBaseControl IO m => m a -> (SomeException -> m a) -> m aSource

A version of catch which is specialized for any exception. This simplifies usage as no explicit type signatures are necessary.

Since 0.5.6

handleAny :: MonadBaseControl IO m => (SomeException -> m a) -> m a -> m aSource

A version of handle which is specialized for any exception. This simplifies usage as no explicit type signatures are necessary.

Since 0.5.6

tryAny :: MonadBaseControl IO m => m a -> m (Either SomeException a)Source

A version of try which is specialized for any exception. This simplifies usage as no explicit type signatures are necessary.

Since 0.5.6

catchIO :: MonadBaseControl IO m => m a -> (IOException -> m a) -> m aSource

A version of catch which is specialized for IO exceptions. This simplifies usage as no explicit type signatures are necessary.

Since 0.5.6

handleIO :: MonadBaseControl IO m => (IOException -> m a) -> m a -> m aSource

A version of handle which is specialized for IO exceptions. This simplifies usage as no explicit type signatures are necessary.

Since 0.5.6

tryIO :: MonadBaseControl IO m => m a -> m (Either IOException a)Source

A version of try which is specialized for IO exceptions. This simplifies usage as no explicit type signatures are necessary.

Since 0.5.6

Force types

Helper functions for situations where type inferer gets confused.

asList :: [a] -> [a]Source

asMap :: Map k v -> Map k vSource

asSet :: Set a -> Set aSource