relude

Logo

GitHub CI Travis AppVeyor Hackage Stackage LTS Stackage Nightly License: MIT

relude is an alternative prelude library. If you find the default Prelude unsatisfying, despite its advantages, consider using relude instead.

Below you can find key design principles behind relude:

  1. 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 from Relude.Unsafe module, but they are not exported by default.

  2. Type-safety. We like to make invalid states unrepresentable. And if it’s possible to express this concept through the types then we do it.

    Example:

    whenNotNull :: Applicative f => [a] -> (NonEmpty a -> f ()) -> f ()
    

    instead of

    whenNotNull :: Applicative f => [a] -> ([a] -> f ()) -> f ()
    
  3. Performance. Prefer Text over String, use spaceleak-free functions (like our custom sum and product), introduce {-# INLINE #-} and {-# SPECIALIZE #-} pragmas where appropriate.

  4. Minimalism (low number of dependencies). We don’t force users of relude to stick to some specific lens or text formatting or logging library. If possible, relude tries to depend only on boot libraries. Dependency graph of relude can give you clearer picture.

  5. Convenience (e.g lifted to MonadIO functions, more reexports). Despite minimalism, we want to bring common types and functions (like containers and bytestring) into scope because they are used in almost every application anyways.

  6. Provide excellent documentation.

  7. User-friendliness. Ability to quickly migrate to relude if you’re familiar with the common libraries like text and containers.

  8. Exploration. Experiment with new ideas and proposals without introducing breaking changes. relude uses the approach with Extra.* 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:

  1. When to use an alternative prelude?
  2. Get started
  3. Difference from Prelude
  4. Reexports
  5. What’s new?
  6. Migration guide
  7. Comparison with other alternative preludes
  8. 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.

When to use an alternative prelude?

The module with the name Prelude is a module imported by default in every Haskell source file of your project. If you want to use some data types or functions which are not exposed by Prelude, you need to import them, adding necessary libraries to your project dependencies. Unlike ordinary libraries, alternative preludes provide different set of available by default functions and data types.

Replacing default Prelude from base has the following disadvantages:

  1. Increased threshold entrance: you need to learn a different standard library.
    • relude tries to lower this threshold as much as possible: excellent documentation, no custom abstractions, behavior is changed only for a small subset of functions.
  2. Extra dependencies: adding more libraries to dependencies increases build times and maintenance burden.
    • relude depends only on boot libraries (almost) which results in small build time, follows PvP and cares about backwards compatibility.

However, using an alternative prelude, specifically relude, has the following advantages:

  1. Increased code safety: no partial functions, no space-leak functions.
  2. Increased productivity: no need to import common functions and data types, more common idioms provided.
  3. Increased performance: some functions in relude are faster than in default Prelude.

Our recommendations when to use relude:

  1. When you develop an application (e.g. CLI tool, web-app). In that case greater productivity is more important than a low number of dependencies.
  2. When writing a big framework. Some of them can be bigger than applications.

Get started

If you want to start using relude in your project and explore it with the help of the 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:

  1. Replace the base dependency with corresponding version of base-noprelude in your .cabal file.
  2. Add a relude dependency to your .cabal file.
  3. Add the following Prelude module to your project (both to filesystem and to exposed-modules):
    module Prelude
           ( module Relude
           ) where
    
    import Relude
    

    NOTE: if you use summoner to generate Haskell project, this tool can automatically create such structure for you when you specify custom prelude.

  4. Optionally modify your Prelude to include more or less functions. Probably you want to hide something from Relude module. Or maybe you want to add something from Relude.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

Main differences from Prelude can be grouped into the following categories:

  • Changed behavior of common functions
    • head, tail, last, init work with NonEmpty a instead of [a].
    • lines, unlines, words, unwords work with Text instead of String.
    • show is polymorphic over return type.
    • Functions sum and product are strict now, which makes them more efficient.
    • You can’t call elem and notElem functions over Set and HashSet. These functions are forbidden for these two types because of the performance reasons.
    • error takes Text
    • undefined triggers a compiler warning, because you probably don’t want to leave undefined in your code. Either use throwIO, Except, error or bug.
  • Not reexported
    • read
    • lookup for lists
    • log
  • Completely new functions are brougth into scope
  • New reexports
    • See Reexports section for a detailed overview.

Reexports

relude reexports some parts of the following libraries:

If you want to clean up imports after switching to relude, you can use relude-specific .hlint.yaml configuration for this task.

base

Multiple sorting functions are available:

  • 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).

readMaybe and readEither are like read but total and give either Maybe or Either with parse error.

(&) – reverse application. x & f & g instead of g $ f $ x is useful sometimes.

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.

  • first and second functions apply a function to first/second part of a tuple (for tuples).
  • bimap takes 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.

transformers & 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 viaNonEmpty function to get Maybe a.

    • viaNonEmpty head :: [a] -> Maybe a
  • uncons splits a list at the first element.

  • ordNub and sortNub are O(n log n) versions of nub (which is quadratic) and hashNub and unstableNub are almost O(n) versions of nub.

  • whenM, unlessM, ifM, guardM are 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
    
  • 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 also forM_ but for_ looks a bit nicer.

    for_ [1..10] $ \i -> do
        ...
    
  • andM, allM, anyM, orM are monadic version of corresponding functions from base.

  • Conversions between Either and Maybe like rightToMaybe and maybeToLeft with clear semantic.

  • using(Reader|State)[T] functions as aliases for flip run(Reader|State)[T].

  • One type class for creating singleton containers. Even monomorhpic ones like Text.

  • evaluateWHNF and evaluateNF functions as clearer and lifted aliases for evaluate and evaluate . force.

  • MonadFail instance for Either.

Need to import explicitly

  • Convenient functions to work with (Bounded a, Enum a) types:

    1. universe :: (Bounded a, Enum a) => [a]: get all values of the type.
    2. inverseMap :: (Bounded a, Enum a, Ord k) => (a -> k) -> k -> Maybe a: convert functions like show to 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"
    
  • Foldable1 typeclass that contains generalized interface for folding non-empty structures like NonEmpty.

  • Validation data type as an alternative to Either when you want to combine all errors.

  • StaticMap and DynamicMap type classes as a general interface for Map-like data structures.

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.

  1. Enable -XOverloadedStrings extension by default for your project.

  2. Since head, tail, last and init work for NonEmpty you should refactor your code in one of the multiple ways described below:

    1. Change [a] to NonEmpty a where it makes sense.
    2. Use functions which return Maybe. There is the viaNonEmpty function for this. And you can use it like viaNonEmpty last l.
      • tail is drop 1. It’s almost never a good idea to use tail from Prelude.
    3. Add import qualified Relude.Unsafe as Unsafe and replace function with qualified usage.
  3. If you use fromJust or !! you should use them from import qualified Relude.Unsafe as Unsafe.

  4. If you use foldr or forM_ or similar for something like Maybe a or Either a b it’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 ()
  5. Forget about String type.

    • Replace (++) with (<>) for String-like types.
    • Use toText/toLText/toString functions to convert to Text/LazyText/String types.
    • Use encodeUtf8/decodeUtf8 to convert to/from ByteString.
    • Use (putStr[Ln]|readFile|writeFile|appendFile)[Text|LText|BS|LBS] functions.
  6. Since show doesn’t come from Show anymore, you need to export Text.Show module if you want to implement Show instance manually. This can be done like this:

import qualified Text.Show
  1. Run hlint using .hlint.yaml file from relude package 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:

  1. Find the commit hash of the relude version you are using (can be found in releases).
  2. Run the command that downloads .hlint.yaml for that version.
  3. Run hlint using 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/v0.6.0.0/.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:

  1. Protolude supports older GHC versions (from GHC 7.6.1) while relude only supports from GHC 8.0.2. So if you aim ancient GHC versions, protolude might 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.
  2. relude has 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 Prelude and just general description of the whole package and libraries it depends on.
  3. relude has 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.
  4. relude has less dependencies and is slightly lighter because of that but still very powerful and useful.
  5. One minor difference: head in protolude returns Maybe a while in relude it works with NonEmpty.
  6. Minor feature: relude uses type-level magic to forbid elem and notElem functions for Set and HashSet (because elem from Foldable run in O(n) time and you can accidentally use elem from Foldable but with relude you can’t).
  7. relude is opt-in oriented and has a notion of Extra.* modules that are not exported by default from the Relude module. 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 Text and much more. It’s very easy to make them accessible package-wide with base-noprelude trick!

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 9.0.0 is required, so make sure that the previous command installed dhall-json >= 1.4.0.

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:

Changes

Changelog

relude uses PVP Versioning. The changelog is available on GitHub.

0.6.0.0 — Oct 30, 2019

  • #171: Add custom type errors to various functions and instances.

    • head, tail, last, init
    • words, unwords, lines, unlines
    • error
    • ToText, ToLText, ToString instances for bytestrings
    • Foldable1 instance for ordinary lists
    • Monad instance for Validation

    (by @vrom911, @chshersh)

  • #164: Reexport ShortByteString, toShort/fromShort functions. (by @vrom911)

  • #182: Support GHC-8.8.1. (by @chshersh)

  • #168, #197: Improve documentation significantly (more and better examples, better wording). (by @chshersh, @vrom911, @Cmdv)

  • #177: Improve usage of performance pragmas. (by @chshersh)

  • #167: Rename functions (and deprecate old versions):

    • prec to prev
    • dupe to dup

    (by @Cmdv, @chshersh)

  • #192: Reexport foldMap' from Data.Foldable. (by @tfausak)

  • #201: Implement !!? as a safe equivalent of !! that returns a Maybe. (by @kutyel)

  • #203: Implement the guarded combinator. (by @JonathanLorimer)

  • #214: Add mapMaybeM function. (by @vrom911)

  • #174: Implement bimapBoth in Relude.Extra.Tuple module, mark mapBoth as DEPRECATED. (by @astynax)

  • #221: Improve documentation for the Validation module significantly. (by @chshersh)

  • #176: Implement property-based tests for Validation laws. (by @astynax)

  • #172: Add Monoid and Semigroup instances for the Validation type. (by @mauriciofierrom)

  • #156: Implement helper type-level functions in Relude.Extra.Type. (by @TheMatten)

  • #170: Implement Elem type family. (by @kutyel)

  • #165: Re-export GHC.Float.atan2. (by @ethercrow)

  • #155: Implement foldlSC — short-circuting list fold — in Relude.Extra.Foldable. (by @josephcsible)

  • #158: Support GHC-8.6.5. (by @chshersh)

  • #148: Migrate HLint rules to the latest Dhall spec. (by @vrom911)

  • #178: Made die be polymorphic in its return type. (by @ilyakooo0)

  • #162, #189, #190, #191, #193, #194, #195: Various refactorings and code improvements:

    • Breaking change: Reorder type parameters to asumMap
    • Implement andM, orM, allM, and anyM in terms of &&^ and ||^
    • Use foldr instead of explicit recursion and toList
    • Use mapToFst instead of zip to improve list fusion in inverseMap
    • Implement foldMap1 for NonEmpty in terms of foldr
    • Use $> instead of *> and pure where possible
    • Implement asumMap and foldMapA by coercing foldMap
    • Return Failure early in <* and *> too

    (by @josephcsible)

  • #187: Remove tasty and tasty-hedgehog dependencies and their redundant imports. (by @dalpd)

0.5.0 — Mar 18, 2019

  • #127: Implement Relude.Extra.Lens module.
  • #125: Moved many numerical functions and types in Relude.Numeric. Reexport toIntegralSized from Data.Bits. Add integerToBounded and integerToNatural in Relude.Numeric.
  • #121: Reexport Ap from Data.Monoid. Change definition of foldMapA to use Ap.
  • #129: Add appliedTo and chainedTo as named versions of operators =<< and <**>.
  • #138: Add RealFloat to Relude.Numeric.
  • #144: Add traverseToSnd and friends to Relude.Extra.Tuple.
  • #140: Improve text of custom compile-time error messages for elem functions.
  • #136: Cover Relude.Extra.* modules with custom HLint rules.
  • #146: Improve documentation for Relude.File file: be more explicit about system locale issues.
  • Improve documentation for One typeclass and add tests.
  • Support ghc-8.6.4 and ghc-8.4.4. Drop support for ghc-8.6.1 and ghc-8.4.3.

0.4.0 — Nov 6, 2018

  • #70: Reexport Contravariant for GHC >= 8.6.1.
  • #103: Drop utf8-string dependency and improve performance of conversion functions.
  • #98: Reexport Bifoldable related stuff from base.
  • #99: Reexport Bitraversable related stuff from base.
  • #100: Add Relude.Extra.Validation with Validationdata type.
  • #89: Add Relude.Extra.Type module containing a typeName function.
  • #92 Add Relude.Extra.Tuple module, containing dupe, mapToFst, mapToSnd, and mapBoth functions.
  • #97: Add (&&^) and (||^) operators.
  • #81: Add asumMap to Foldable functions.
  • #80: Add hlint rules for whenLeft, whenLeftM, whenRight and whenRightM.
  • #79: Add HLint rules for One typeclass.
  • Remove openFile and hClose.
  • #83: Make documentation for nub functions prettier.
  • #109: Use Dhall v3.0.0 for hlint file generation.

0.3.0

  • #41: Add Foldable1.

  • #64: Remove Print typeclass. Add put[L]BS[Ln] functions. trace functions now take String as argument instead of Text.

    Important: this is a breaking change. If you used polymorphic putStrLn you need to remove type application or switch to one of the monomorphic functions. Also, you can’t abstract over Print typeclass anymore.

  • #66: Export (>>>) and (<<<) from Control.Category.

  • #59: Introduce flap function and its operator version ??.

  • #64: Improve performance of functions from Foldable1. Add foldl1' function.

  • Reexport uncons from base.

  • Rewrite die implementation to use die from base.

  • #19: Rewrite .hlint.yaml to Dhall.

  • Move stdin- and stdout-related functions to new module Relude.Lifted.Terminal.

  • #67: Add HLint rules for put* functions.

  • #22: readFile, writeFile and appendFile now work with String. Add lifted version of hClose. Add readFile, writeFile and appendFile alternatives for Text and ByteString.

  • #61: Add under2 and underF2 functions to Relude.Extra.Newtype.

  • #60: Add hoistMaybe and hoistEither functions.

0.2.0

  • #43: Implement Relude.Extra.Newtype module.
  • #46: Add a function that returns its own name.
  • #48: Export <&> from base. Also reexport fromLeft and fromRight from base where possible.
  • #49: Speed up and refactor property tests.
  • #54: Improve documentation. Add more examples to documentation and more tests. Reexport withReader and withReaderT. Remove safeHead. Rename Relude.List.Safe to Relude.List.NonEmpty.

0.1.1

  • #44: Implement parser deriviation from pretty-printers.

0.1.0

  • #7: Remove Container.Class.Container. Export Foldable.
  • #2: Remove microlens from dependencies.
  • #10: Remove VarArg module.
  • #9: Remove safe-exceptions from dependencies. Reexport Exception and SomeException from Control.Exception instead.
  • #11: Remove TypeOps module and type-operators dependency.
  • #13: Remove list, getContents, interact, getArgs, note functions. Remove Lifted.ST module. Rename Lifted.Env to Lifted.Exit.
  • #16: Rename whenLeft, whenRight, whenLeftM, whenRightM to whenLeft_ and whenRight_, whenLeftM_ and whenRightM_. Add whenLeft, whenRight, whenLeftM, whenRightM which return the value.
  • #18: Add LazyStrict type class for conversions.
  • map is not fmap anymore. Reexport map from Data.List
  • #12: Remove liquid-haskell support.
  • #20: Add viaNonEmpty function.
  • #21: Add MonadFail instance for Either.
  • #17: Add foldMapA and foldMapM functions.
  • #4: Rename package to Relude.
  • #14: Add Relude.Extra.* modules which are not exported by default but have useful functions.
  • #8: Introduce StaticMap and DynamicMap type classes as universal interface for Map-like structures.