relude
Custom prelude from Kowainik
https://github.com/kowainik/relude
| Version on this page: | 0.4.0 |
| LTS Haskell 24.24: | 1.2.2.2@rev:1 |
| Stackage Nightly 2025-12-15: | 1.2.2.2@rev:1 |
| Latest on Hackage: | 1.2.2.2@rev:1 |
relude-0.4.0@sha256:2d31e2536b43625176f124bdbcf9d5dbae60084c9ec93c66663436033e6eeaef,8348Module documentation for 0.4.0
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 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 (likecontainersandbytestring) into scope because they are used in almost every application anyways. -
Provide excellent documentation.
- Tutorial
- Migration guide from
Prelude - Haddock with examples for (almost) every function
(all examples are tested with
doctest) - Documentation regarding internal module structure
relude-specific HLint rules:.hlint.yaml
-
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:
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 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 ReludeNOTE: 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.
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 withNonEmpty ainstead of[a].undefinedtriggers a compiler warning, because you probably don’t want to leaveundefinedin your code. Either usethrowIO,Except,errororbug.- 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 likesortWith, but more time-efficient if function is calculated slowly (though less space-efficient). So you should writesortOn length(would sort elements by length) butsortWith fst(would sort list of pairs by first element).
- Functions
sumandproductare strict now, which makes them more efficient. - 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. errortakesText.lookupfor lists is not exported.
Reexports ↑
relude reexports some parts of the following libraries:
basecontainersunordered-containerstextbytestringtransformersmtldeepseqstm
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.
firstandsecondfunctions 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.
transforms & mtl
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 xAfter:
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 likeshowto 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.
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.tailisdrop 1. It’s almost never a good idea to usetailfromPrelude.
- Add
import qualified Relude.Unsafe as Unsafeand replace function with qualified usage.
- Change
-
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 -> afromMaybe :: a -> Maybe a -> amaybeToList :: Maybe a -> [a]maybeToMonoid :: Monoid m => Maybe m -> mmaybe :: b -> (a -> b) -> Maybe a -> bwhenJust :: Applicative f => Maybe a -> (a -> f ()) -> f ()whenJustM :: Monad m => m (Maybe a) -> (a -> m ()) -> m ()
-
EitherfromLeft :: a -> Either a b -> afromRight :: b -> Either a b -> beither :: (a -> c) -> (b -> c) -> Either a b -> cwhenRight_ :: 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. - 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. - Use
(putStr[Ln]|readFile|writeFile|appendFile)[Text|LText|BS|LBS]functions.
- Replace
-
Run
hlintusing.hlint.yamlfile fromreludepackage to cleanup code and imports.
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.
Changes
Change log
Unreleased
0.4.0 — Nov 6, 2018
- #70:
Reexport
Contravariantfor GHC >= 8.6.1. - #103:
Drop
utf8-stringdependency and improve performance of conversion functions. - #98:
Reexport
Bifoldablerelated stuff frombase. - #99:
Reexport
Bitraversablerelated stuff frombase. - #100:
Add
Relude.Extra.ValidationwithValidationdata type. - #89:
Add
Relude.Extra.Typemodule containing atypeNamefunction. - #92
Add
Relude.Extra.Tuplemodule, containingdupe,mapToFst,mapToSnd, andmapBothfunctions. - #97:
Add
(&&^)and(||^)operators. - #81:
Add
asumMaptoFoldablefunctions. - #80:
Add hlint rules for
whenLeft,whenLeftM,whenRightandwhenRightM. - #79:
Add HLint rules for
Onetypeclass. - Remove
openFileandhClose. - #83:
Make documentation for
nubfunctions prettier. - #109: Use Dhall v3.0.0 for hlint file generation.
0.3.0
-
#41: Add
Foldable1. -
#64: Remove
Printtypeclass. Addput[L]BS[Ln]functions.tracefunctions now takeStringas argument instead ofText.Important: this is a breaking change. If you used polymorphic
putStrLnyou need to remove type application or switch to one of the monomorphic functions. Also, you can’t abstract overPrinttypeclass anymore. -
#66: Export
(>>>)and(<<<)fromControl.Category. -
#59: Introduce
flapfunction and its operator version??. -
#64: Improve performance of functions from
Foldable1. Addfoldl1'function. -
Reexport
unconsfrombase. -
Rewrite
dieimplementation to usediefrombase. -
#19: Rewrite
.hlint.yamlto Dhall. -
Move
stdin- andstdout-related functions to new moduleRelude.Lifted.Terminal. -
#67: Add HLint rules for
put*functions. -
#22:
readFile,writeFileandappendFilenow work withString. Add lifted version ofhClose. AddreadFile,writeFileandappendFilealternatives forTextandByteString. -
#61: Add
under2andunderF2functions toRelude.Extra.Newtype. -
#60: Add
hoistMaybeandhoistEitherfunctions.
0.2.0
- #43:
Implement
Relude.Extra.Newtypemodule. - #46: Add a function that returns its own name.
- #48:
Export
<&>frombase. Also reexportfromLeftandfromRightfrombasewhere possible. - #49: Speed up and refactor property tests.
- #54:
Improve documentation.
Add more examples to documentation and more tests.
Reexport
withReaderandwithReaderT. RemovesafeHead. RenameRelude.List.SafetoRelude.List.NonEmpty.
0.1.1
- #44: Implement parser deriviation from pretty-printers.
0.1.0
- #7:
Remove
Container.Class.Container. ExportFoldable. - #2:
Remove
microlensfrom dependencies. - #10:
Remove
VarArgmodule. - #9:
Remove
safe-exceptionsfrom dependencies. ReexportExceptionandSomeExceptionfromControl.Exceptioninstead. - #11:
Remove
TypeOpsmodule andtype-operatorsdependency. - #13:
Remove
list,getContents,interact,getArgs,notefunctions. RemoveLifted.STmodule. RenameLifted.EnvtoLifted.Exit. - #16:
Rename
whenLeft,whenRight,whenLeftM,whenRightMtowhenLeft_andwhenRight_,whenLeftM_andwhenRightM_. AddwhenLeft,whenRight,whenLeftM,whenRightMwhich return the value. - #18:
Add
LazyStricttype class for conversions. mapis notfmapanymore. ReexportmapfromData.List- #12:
Remove
liquid-haskellsupport. - #20:
Add
viaNonEmptyfunction. - #21:
Add
MonadFailinstance forEither. - #17:
Add
foldMapAandfoldMapMfunctions. - #4:
Rename package to
Relude. - #14:
Add
Relude.Extra.*modules which are not exported by default but have useful functions. - #8:
Introduce
StaticMapandDynamicMaptype classes as universal interface for Map-like structures.
relude uses PVP Versioning.
The change log is available on GitHub.