relude: Custom prelude from Kowainik

[ library, mit, prelude ] [ Propose Tags ]

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 from Relude.Unsafe module, 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 ()

  • Performance. Prefer Text over String, use spaceleak-free functions (like our custom sum and product).

  • Minimalism (low number of dependencies). We don't force users of relude to stick to some specific lens or text formatting or logging library.

  • Convenience (like lifted to MonadIO functions, more reexports). But we want to bring common types and functions (like containers and bytestrng) into scope because they are used in almost every application anyways.

  • Provide excellent documentation.

  1. Tutorial

  2. Migration guide from Prelude

  3. Haddock with examples for (almost) every function (all examples are tested with <code>doctest</code>)

  4. Documentation regarding internal module structure)

  5. relude-specific HLint rules: .hlint.yaml

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

  • Exploration. Experiment with new ideas and proposals without introducing breaking changes.


[Skip to Readme]

Downloads

Note: This package has metadata revisions in the cabal description newer than included in the tarball. To unpack the package including the revisions, use 'cabal get'.

Maintainer's Corner

Package maintainers

For package maintainers and hackage trustees

Candidates

Versions [RSS] 0.1.0, 0.1.1, 0.2.0, 0.3.0, 0.4.0, 0.5.0, 0.6.0.0, 0.7.0.0, 1.0.0.0, 1.0.0.1, 1.1.0.0, 1.2.0.0, 1.2.1.0
Change log CHANGELOG.md
Dependencies base (>=4.9 && <4.16), bytestring, containers, deepseq, ghc-prim (>=0.4.0.0), hashable, mtl, stm, text, transformers, unordered-containers, utf8-string [details]
License MIT
Copyright 2016 Stephen Diehl, 2016-2018 Serokell, 2018 Kowainik
Author Stephen Diehl, @serokell, Kowainik
Maintainer Kowainik <xrom.xkov@gmail.com>
Revised Revision 2 made by sjakobi at 2022-09-07T05:19:55Z
Category Prelude
Home page https://github.com/kowainik/relude
Bug tracker https://github.com/kowainik/relude/issues
Source repo head: git clone git@github.com:kowainik/relude.git
Uploaded by shersh at 2018-08-19T06:25:39Z
Distributions Arch:1.2.0.0, Fedora:1.2.0.0, LTSHaskell:1.2.1.0, NixOS:1.2.1.0, Stackage:1.2.1.0
Reverse Dependencies 88 direct, 43 indirect [details]
Downloads 16662 total (199 in the last 30 days)
Rating 2.5 (votes: 3) [estimated by Bayesian average]
Your Rating
  • λ
  • λ
  • λ
Status Docs available [build log]
Last success reported on 2018-08-19 [all 1 reports]

Readme for relude-0.2.0

[back to package description]

Relude

Relude: cyclone logo Build Status Hackage Stackage LTS Stackage Nightly License: MIT

relude is a custom prelude, an alternative to default Prelude. relude tries to achieve the following goals:

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

  5. Convenience (like lifted to MonadIO functions, more reexports). But we want to bring common types and functions (like containers and bytestrng) 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. Get started.
  2. Difference from Prelude.
  3. Reexports.
  4. What's new?
  5. 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.

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:

  1. Replace base dependency with corresponding version of base-noprelude in your .cabal file.
  2. 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.

  3. 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.

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, init work with NonEmpty a instead of [a].
  • undefined triggers a compiler warning, because you probably don't want to leave undefined in your code. Either use throwIO, Except, error or 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 sum and product are strict now, which makes them more efficient.
  • If you try to do something like putStrLn "hi", you'll get an error message if OverloadedStrings is enabled – it happens because the compiler doesn't know what type to infer for the string. Use putTextLn in this case.
  • Since show doesn't come from Show anymore, you need to export Show from Text.Show module if you want to implement Show instance manually.
  • 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.
  • lookup for lists is not exported.

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.

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

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

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

  • 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
    
  • readMaybe and readEither are like read but total and give either Maybe or Either with 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 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.

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

  • 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"
    
  • A lot of other cool things:

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.

  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 putStr and putStrLn with putText and putTextLn.
    • Replace (++) with (<>) for String-like types.
    • Try to use fmt library if you need to construct messages.
    • Use toText/toLText/toString functions to convert to Text/LazyText/String types.
    • Use encodeUtf8/decodeUtf8 to convert to/from ByteString.
  6. Run hlint using .hlint.yaml file from relude package to cleanup code and imports.

Acknowledgement

Icons made by Freepik from www.flaticon.com is licensed by CC 3.0 BY.