Relude
 
 
 
 

relude is a custom prelude based on universum. relude tries to achieve the following goals:
- 
Avoid all partial functions
(like head :: [a] -> a). The types of partial functions lie about their
behavior and usage of such functions can lead to the unexpected bugs. Though
you can still use some unsafe functions fromRelude.Unsafemodule, but they
are not exported by default.
 
- 
Type-safety. We like to make invalid states unrepresantable. And if it's
possible to express this concept through the types then we will do it. Example: whenNotNull :: Applicative f => [a] -> (NonEmpty a -> f ()) -> f ()
 instead of whenNotNull :: Applicative f => [a] -> ([a] -> f ()) -> f ()
 
- 
Performance. Prefer TextoverString,
use spaceleak-free functions (like our customsumandproduct), introduce{-# INLINE #-}and{-# SPECIALIZE #-}pragmas where appropriate.
 
- 
Minimalism (low number of dependencies). We don't force users of reludeto
stick to some specific lens or text formatting or logging library.
 
- 
Convenience (like lifted to MonadIOfunctions, more reexports). But we
want to bring common types and functions (likecontainersandbytestrng)
into scope because they are used in almost every application anyways.
 
- 
Provide excellent documentation. 
- 
User-friendliness. Ability to quickly migrate to reludeif you're familiar
with the common libraries liketextandcontainers.
 
- 
Exploration. Experiment with new ideas and proposals without introducing
breaking changes. 
This README contains introduction to Relude and a tutorial on how to use it.
Structure of this tutorial
This tutorial has several parts:
- Motivation.
- Get started.
- Difference from Prelude.
- Reexports.
- What's new?
- Migration guide.
This is neither a tutorial on Haskell nor tutorial on each function contained
in Relude. For detailed documentation of every function together with examples
and usage, see Haddock documentation.
Motivation ↑
We decided to base relude on universum due to the following reasons:
- universumhelps to achieve our goals more than any other custom prelude.
- We worked on universuma lot (just check contributors statistics) and we
know its internal structure.
The motivation to create another alternative prelude instead of modifying
existing one is that it's hard to change preludes in any way. relude
uses approach with Extra.* modules which are not exported by default so it's
quite easy to bring something new (that satisfies relude goals) and let users
decide to use it or not.
Unlike universum, we are:
- Not trying to replace Foldablewith customContainertype class. We only
forbidelemandnotElemfunctions for sets due to performance reasons.
- Have less dependencies: no vector, nomicrolens, nosafe-exceptions, notype-operators.
- Have a lot of other different improvements.
Get started ↑
If you want to start using relude in your project and explore it with the help
of compiler, set everything up according to the instructions below.
base-noprelude
This is the recommended way to use custom prelude. It requires you to perform
the following steps:
- Replace basedependency with corresponding version ofbase-nopreludein
your.cabalfile.
- Add the following Preludemodule to your project (both to filesystem and toexposed-modules):module Prelude
       ( module Relude
       ) where
import Relude
 
- Optionally modify your Preludeto include more or less functions. Probably
you want to hide something fromReludemodule. Or maybe you want to add
something fromRelude.Extra.*modules!
This is a very convenient way to add a custom prelude to your project because
you don't need to import module manually inside each file and enable the
NoImplicitPrelude extension.
Per-file configuration
Disable the built-in prelude at the top of your file:
{-# LANGUAGE NoImplicitPrelude #-}
Or directly in your project .cabal file, if you want to use in every module by default:
default-extensions: NoImplicitPrelude
Then add the following import to your modules:
import Relude
Difference from Prelude ↑
- head,- tail,- last,- initwork with- NonEmpty ainstead of- [a].
- undefinedtriggers a compiler warning, because you probably don't want to
leave- undefinedin your code. Either use- throwIO,- Except,- erroror- bug.
- Multiple sorting functions are available without imports:
- sortBy :: (a -> a -> Ordering) -> [a] -> [a]: sorts list using given custom comparator.
- sortWith :: Ord b => (a -> b) -> [a] -> [a]: sorts a list based on some property of its elements.
- sortOn :: Ord b => (a -> b) -> [a] -> [a]: just like- sortWith, but more
time-efficient if function is calculated slowly (though less
space-efficient). So you should write- sortOn length(would sort elements
by length) but- sortWith fst(would sort list of pairs by first element).
 
- Functions sumandproductare strict now, which makes them more efficient.
- If you try to do something like putStrLn "hi", you'll get an error message ifOverloadedStringsis enabled – it happens because the compiler doesn't know what
type to infer for the string. UseputTextLnin this case.
- Since showdoesn't come fromShowanymore, you need to exportShowfromText.Showmodule if you want to implementShowinstance manually.
- You can't call elemandnotElemfunctions overSetandHashSet. These
functions are forbidden for these two types because of the performance reasons.
- errortakes- Text.
- lookupdoesn't work on list of pairs.
Reexports ↑
Commonly used libraries
First of all, we reexport some generally useful modules: Control.Applicative,
Data.Traversable, Data.Monoid, Control.DeepSeq, Data.List, and lots of
others. Just remove unneeded imports after importing Relude (you can use
.hlint.yaml file for this).
Then, some commonly used types: Map/HashMap/IntMap, Set/HashSet/IntSet,
Seq, Text and ByteString (as well as synonyms LText and LByteString
for lazy versions).
liftIO and MonadIO are exported by default. A lot of IO functions are
generalized to MonadIO.
deepseq is exported. For instance, if you want to force deep evaluation of
some value (in IO), you can write evaluateNF a. WHNF evaluation is possible
with evaluateWHNF a.
We also reexport big chunks of these libraries: mtl, stm.
Bifunctor
type class with useful instances is exported.
- firstand- secondfunctions apply a function to first/second part of a tuple (for tuples).
- bimaptakes two functions and applies them to first and second parts respectively.
Text
We export Text and LText, and some functions work with Text instead of String –
specifically, IO functions (readFile, putStrLn, etc) and show. In fact, show
is polymorphic and can produce strict or lazy Text, String, or ByteString.
Also, toText/toLText/toString can convert Text|LText|String types to
Text/LText/String. If you want to convert to and from ByteString use
encodeUtf8/decodeUtf8 functions.
Debugging and undefineds
trace, traceM, traceShow, etc. are available by default. GHC will warn you
if you accidentally leave them in code, however (same for undefined).
We also have data Undefined = Undefined (which, too, comes with warnings).
Exceptions
TODO: write about reexports, Bug and Exc pattern.
What's new? ↑
Finally, we can move to part describing the new cool features we bring with relude.
- 
Safe analogue for headfunction:safeHead :: [a] -> Maybe aor you can
use ourviaNonEmptyfunction to getMaybe a:viaNonEmpty head :: [a] -> Maybe a.
 
- 
unconssplits a list at the first element.
 
- 
ordNubandsortNubare O(n log n) versions ofnub(which is quadratic)
andhashNubandunstableNubare almost O(n) versions ofnub.
 
- 
(&)– reverse application.x & f & ginstead ofg $ f $ xis useful sometimes.
 
- 
whenM,unlessM,ifM,guardMare available and do what you expect
them to do (e.g.whenM (doesFileExist "foo")).
 
- 
General fold functions: foldMapA :: (Monoid b, Applicative m, Foldable f) => (a -> m b) -> f a -> m b
foldMapM :: (Monoid b, Monad m, Foldable f) => (a -> m b) -> f a -> m b
 
- 
readMaybeandreadEitherare likereadbut total and give eitherMaybeorEitherwith parse error.
 
- 
when(Just|Nothing|Left|Right|NotEmpty)[M][_]let you conditionally execute something. Before:
 case mbX of
    Nothing -> return ()
    Just x  -> f x
 After: whenJust mbX $ \x ->
    f x
 
- 
for_for loops. There's alsoforM_butfor_looks a bit nicer.
 for_ [1..10] $ \i -> do
    ...
 
- 
andM,allM,anyM,orMare monadic version of corresponding functions frombase.
 
- 
Conversions between EitherandMaybelikerightToMaybeandmaybeToLeftwith clear semantic.
 
- 
using(Reader|State)[T]functions as aliases forflip run(Reader|State)[T].
 
- 
Onetype class
for creating singleton containers. Even monomorhpic ones likeText.
 
- 
StaticMapandDynamicMaptype classes as a
general interface forMap-like data structures.
 
- 
evaluateWHNFandevaluateNFfunctions as clearer and lifted aliases forevaluateandevaluate . force.
 
- 
MonadFailinstance forEither.
 
Migration guide ↑
In order to replace default Prelude with relude you should start with instructions given in
get started section.
This section describes what you need to change to make your code compile with relude.
- 
Enable -XOverloadedStringsextension by default for your project.
 
- 
Since head,tail,lastandinitwork forNonEmptyyou should
refactor your code in one of the multiple ways described below:
 
- Change [a]toNonEmpty awhere it makes sense.
- Use functions which return Maybe. There is theviaNonEmptyfunction for this.
And you can use it likeviaNonEmpty last l.
- viaNonEmpty head lis- safeHead l
- tailis- drop 1. It's almost never a good idea to use- tailfrom- Prelude.
 
- Add import qualified Relude.Unsafe as Unsafeand replace function with qualified usage.
 
- 
If you use fromJustor!!you should use them fromimport qualified Relude.Unsafe as Unsafe.
 
- 
If you use foldrorforM_or similar for something likeMaybe aorEither a bit's recommended to replace usages of such function with
monomorhpic alternatives:
 
- 
Maybe
 
- (?:)          :: Maybe a -> a -> a
- fromMaybe     :: a -> Maybe a -> a
- maybeToList   :: Maybe a -> [a]
- maybeToMonoid :: Monoid m => Maybe m -> m
- maybe         :: b -> (a -> b) -> Maybe a -> b
- whenJust      :: Applicative f => Maybe a -> (a -> f ()) -> f ()
- whenJustM     :: Monad m => m (Maybe a) -> (a -> m ()) -> m ()
 
- 
Either
 
- fromLeft   :: a -> Either a b -> a
- fromRight  :: b -> Either a b -> b
- either     :: (a -> c) -> (b -> c) -> Either a b -> c
- whenRight_  :: Applicative f => Either l r -> (r -> f ()) -> f ()
- whenRightM_ :: Monad m => m (Either l r) -> (r -> m ()) -> m ()
 
 
- 
Forget about Stringtype.
 
- Replace putStrandputStrLnwithputTextandputTextLn.
- Replace (++)with(<>)forString-like types.
- Try to use fmtlibrary if you need to construct messages.
- Use toText/toLText/toStringfunctions to convert toText/LazyText/Stringtypes.
- Use encodeUtf8/decodeUtf8to convert to/fromByteString.
 
- 
Run hlintusing.hlint.yamlfile fromreludepackage to cleanup code and imports.