Relude
 
 
 
 
 
 

relude is a custom prelude, an alternative to default Prelude.
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 unrepresentable. 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 (likecontainersandbytestring)
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. reludeuses the approach withExtra.*modules which are not
exported by default so it's quite easy to bring something new and let users
decide to use it or not.
 
This README contains introduction to Relude and a tutorial on how to use it.
Structure of this tutorial
This tutorial has several parts:
- Get started
- Difference from Prelude
- Reexports
- What's new?
- Migration guide
- Comparison with other alternative preludes
- For developers
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.
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 one of 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 a reludedependency to your.cabalfile.
- Add the following Preludemodule to your project (both to filesystem and toexposed-modules):module Prelude
       ( module Relude
       ) where
import Relude
 
NOTE: if you use summonerto generate Haskell project,
this tool can automatically create such structure for you when you specify custom prelude.
 
 
- 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.
Mixins ↑
You can use Cabal feature mixins to replace the default Prelude with Relude
without need to add extra dependencies or import Relude manually each time.
See the following example:
NOTE: this requires Cabal version to be at least 2.2
cabal-version:       2.2
name:                prelude-example
version:             0.0.0.0
library
  exposed-modules:     Example
  build-depends:       base >= 4.10 && < 4.13
                     , relude ^>= 0.4.0
  mixins:              base hiding (Prelude)
                     , relude (Relude as Prelude)
  default-language:    Haskell2010
If you want to be able to import Extra.* modules when using mixins approach,
you need to list those modules under mixins field as well, like this:
  mixins:              base hiding (Prelude)
                     , relude (Relude as Prelude, Relude.Extra.Enum)
NoImplicitPrelude ↑
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
Add relude as a dependency of your project. Then add the following import to
your modules:
import Relude
Difference from Prelude ↑
Reexports ↑
relude reexports some parts of the following libraries:
- base
- containers
- unordered-containers
- text
- bytestring
- transformers
- mtl
- deepseq
- stm
If you want to clean up imports after switching to relude, you can use
relude-specific .hlint.yaml configuration for this task.
base
Some generally useful modules from base package, like: Control.Applicative,
Data.Traversable, Data.Monoid, Data.List, and lots of others.
liftIO and MonadIO are exported by default. A lot of IO functions are
generalized to MonadIO.
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.
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).
relude reexports Exception type from the base package and introduces the
bug function as an alternative to error. There's also a very convenient
Exc pattern-synonym to handle exceptions of different types.
See Relude.Exception module for details on exceptions.
containers & unordered-containers
The following types from these two packages are exported:
Then, some commonly used types:
- Maps: strict versions of Map,HashMap,IntMap.
- Sets: Set,HashSet,IntSet.
- Sequences: Seq.
text & bytestring
relude exports Text and ByteString (as well as synonyms LText and LByteString
for lazy versions) 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.
The following parts of these two libraries are exported:
- Transformers: State[T],Reader[T],ExceptT,MaybeT.
- Classes: MonadReader,MonadState,MonadError.
Deepseq
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.
What's new? ↑
Finally, we can move to part describing the new cool features we bring with relude.
Available by default
- 
Safe analogue for list functions: use viaNonEmptyfunction 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.
 
Need to import explicitly
- 
Convenient functions to work with (Bounded a, Enum a)types:
 
- universe :: (Bounded a, Enum a) => [a]: get all values of the type.
- inverseMap :: (Bounded a, Enum a, Ord k) => (a -> k) -> k -> Maybe a: convert functions like- showto parsers.
 
- 
Nice helpers to deal with newtypes in a more pleasant way:
 ghci> newtype Foo = Foo Bool deriving Show
ghci> under not (Foo True)
Foo False
 
- 
Functions to operate with CallStack:
 >>> foo :: HasCallStack => String; foo = ownName
>>> foo
"foo"
 
- 
Foldable1typeclass that contains generalized interface for folding
non-empty structures likeNonEmpty.
 
- 
Validationdata type as an alternative toEitherwhen you want to combine
all errors.
 
Explore Extra modules: Relude.Extra
Migration guide ↑
In order to replace default Prelude with relude you should start with instructions given in
get started section.
Code changes
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.
- 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 (++)with(<>)forString-like types.
- Use toText/toLText/toStringfunctions to convert toText/LazyText/Stringtypes.
- Use encodeUtf8/decodeUtf8to convert to/fromByteString.
- Use (putStr[Ln]|readFile|writeFile|appendFile)[Text|LText|BS|LBS]functions.
 
- 
Run hlintusing.hlint.yamlfile fromreludepackage to cleanup code and imports.
 
Running HLint on CI
Instead of storing a relude-specific .hlint.yaml file inside your repository,
you can run HLint with this file automatically on any CI service such as
Travis CI or Circle CI.
For this you need to:
- Find the commit hash of the reludeversion you are using (can be found in releases).
- Run the command that downloads .hlint.yamlfor that version.
- Run hlintusing this file.
For the latest relude version, this can be achieved by executing the following
two commands on your CI:
curl https://raw.githubusercontent.com/kowainik/relude/55968311244690f5cc8b4484a37a63d988ea2ec4/.hlint.yaml -o .hlint-relude.yaml
curl -sSL https://raw.github.com/ndmitchell/neil/master/misc/travis.sh | sh -s -- hlint -h .hlint-relude.yaml .
See an example of this feature being used in Summoner.
Comparison with other alternative preludes ↑
There are quite a few libraries that can be used as alternative preludes in
Haskell, let's compare Relude with some of them.
Relude vs Protolude ↑
Protolude is one of the most popular
alternative preludes. It's also relatively small, but:
- Protolude supports older GHC versions (from GHC 7.6.1) while reludeonly
supports from GHC 8.0.2. So if you aim ancient GHC versions,protoludemight be a better choice. But because of that it contains a lot of CPP, code
is ugly in some places as a consequence and it's more difficult to add,
remove or change things there.
- reludehas much better documentation:- 
- High-level overview of internal module structure
- 100% Haddock coverage
- Almost every function has usage examples and all examples are tested with
doctest(which also sometimes hard to do because of multiple GHC
versions support, but we try really hard)
- Tutorial + migration guide from
Preludeand just general description of the whole package and libraries
it depends on.
 
- reludehas custom HLint rules specific to it: you can use them to remove
redundant imports or find hints how to use functions from- relude. Moreover,
the HLint rules are generated using Dhall and there is a blog post about
this technique.
This allows to maintain HLint rules much easier because it's already not an
easy task.
- reludehas less dependencies and is slightly lighter because of that but still
very powerful and useful.
- One minor difference: headinprotoludereturnsMaybe awhile inreludeit works withNonEmpty.
- Minor feature: reludeuses type-level magic to forbidelemandnotElemfunctions forSetandHashSet(becauseelemfromFoldablerun in
O(n) time and you can accidentally useelemfromFoldablebut withreludeyou can't).
- reludeis opt-in oriented and has a notion of- Extra.*modules that are
not exported by default from the- Reludemodule. So we don't spoil global
namespace but still have a lot of useful features like polymorphic functions
to work with every- newtype,- Enum/Bounded-related useful utilities,
functions to take a name of any type as- Textand much more. It's very easy
to make them accessible package-wide with- base-nopreludetrick!
For Developers ↑
Generating .hlint.yaml
Note, that we are using custom hlint setting which are Relude specific. To
keep it up to date don't forget to reflect your changes in this file. We are
using Dhall to maintain the configurations. To use it follow the steps below.
First time:
$ cabal new-install dhall-json
Dhall 3.0.0 is required, so make sure that the previous command installed
dhall-json >= 1.2.4.
To generate hlint file:
$ dhall-to-yaml --omitNull <<< './hlint/hlint.dhall' > .hlint.yaml
Check that you have generated valid .hlint.yaml file without parse errors:
$ hlint test/Spec.hs
See our blog post where we describe the details of the implementation for this solution:
Acknowledgement
Icons made by Freepik from www.flaticon.com is licensed by CC 3.0 BY.