Copyright | (c) 2016 Stephen Diehl (c) 2016-2018 Serokell (c) 2018-2023 Kowainik |
---|---|
License | MIT |
Maintainer | Kowainik <xrom.xkov@gmail.com> |
Stability | Stable |
Portability | Portable |
Safe Haskell | Safe |
Language | Haskell2010 |
relude
is a safe, performant, user-friendly and lightweight Haskell
standard library.
Relude is the main module that reexports all functionality provided by the library that will replace the default Prelude
in your project.
Usage
To start using relude
in your project, you can set the library up for you by
one of the following ways.
mixins
One of the most convenient ways to use relude
is via the mixins
feature. This
feature is available since Cabal >= 2.2
. In order to use the mixins
feature
one needs to specify supported cabal-version
in your package description.
And then the following lines should be added to the required stanza to replace
default Prelude with relude
.
cabal-version: 2.4 ... library ... mixins: base hiding (Prelude) , relude (Relude as Prelude) , relude
base-noprelude
Alternatively, you can replace base
package in your dependencies with
base-noprelude
and add
the following Prelude module to your package to use relude
by default in
every module instead of base
Prelude:
module Prelude ( module Relude ) where import Relude
NoImplicitPrelude
If you want to use relude
per-module basis then just add next lines to your
module to replace default Prelude:
{-# LANGUAGE NoImplicitPrelude #-} import Relude
Structure
This documentation section contains the description of internal module structure to help navigate between modules, search for interesting functionalities and understand where you need to put your new changes (if you're a contributor).
Functions and types are distributed across multiple modules and grouped by
meaning or category. Name of the module should give you hints regarding what
this module contains. Some categories contain a significant amount of both
reexported
functions and functions of our own. To make it easier to understand these enormous
chunks of functions, all reexported stuff is moved into the separate module with
name Relude.SomeCategory.Reexport
and our own functions and types are in
Relude.SomeCategory.SomeName
. For example, see modules
Relude.Foldable.Fold and Relude.Foldable.Reexport.
Synopsis
- module Relude.Applicative
- module Relude.Base
- module Relude.Bool
- module Relude.Container
- module Relude.Debug
- module Relude.DeepSeq
- module Relude.Enum
- module Relude.Exception
- module Relude.File
- module Relude.Foldable
- module Relude.Function
- module Relude.Functor
- module Relude.Lifted
- module Relude.List
- module Relude.Monad
- module Relude.Monoid
- module Relude.Nub
- module Relude.Numeric
- module Relude.Print
- module Relude.String
Default Modules
module Relude.Applicative
Relude.Applicative contains reexports from Control.Applicative and some general-purpose applicative combinators.
module Relude.Base
Relude.Base contains different general types and type classes from base
package (Char
, Eq
, Generic
, etc.) not exported by other modules.
module Relude.Bool
Relude.Bool contains Bool
data type with different predicates and combinators.
module Relude.Container
Relude.Container provides One
typeclass for creating data structures
from singleton element and reexports of types from packages containers
and
unordered-containers
.
module Relude.Debug
Relude.Debug contains trace
-like debugging functions with compile-time
warnings (so you don't forget to remove them).
module Relude.DeepSeq
Relude.DeepSeq has reexports from Control.DeepSeq module and functions to evaluate expressions to weak-head normal form or normal form.
module Relude.Enum
Relude.Enum reexports Enum
related typeclasses and functions. Also
introduced a few useful helpers to work with Enums.
module Relude.Exception
Relude.Exception contains reexports from Control.Exception, introduces
bug
function as better error
and Exc
pattern synonym for convenient
pattern-matching on exceptions.
module Relude.File
Relude.File implements functions to work with file content as Text
or
ByteString
.
module Relude.Foldable
Relude.Foldable reexports functions for Foldable
and Traversable
and
provide own better alternatives to some existing functions.
module Relude.Function
Relude.Function contains almost everything from the Data.Function module.
module Relude.Functor
Relude.Functor contains reexports from Data.Functor, Data.Bifunctor,
other useful Functor
combinators.
module Relude.Lifted
Relude.Lifted implements lifted to MonadIO
functions to work with
console, files, IORef
s, MVar
s, etc.
module Relude.List
Relude.List provides big chunk of Data.List, NonEmpty
type and
functions for this type (head
, tail
, last
, init
).
module Relude.Monad
Relude.Monad contains functions and data types from Data.Maybe and Data.Either modules, monad transformers and other various combinators.
module Relude.Monoid
Relude.Monoid reexports various types and functions from Data.Monoid and Data.Semigroup.
module Relude.Nub
Relude.Nub implements better versions of nub
function for list.
module Relude.Numeric
Relude.Numeric contains functions and types to work with numerical data.
module Relude.Print
Relude.Print contains printing to terminal functions for Text
and ByteString
.
module Relude.String
Relude.String contains reexports from text
and bytestring
packages
with conversion functions between different textual types.
Extra Modules
The following modules are not exported by default, but you can easily bring them to every module in your package by modifying your Prelude file:
Relude.Extra | Reexports every Relude.Extra.* module |
Relude.Extra.Bifunctor | Additional combinators for Bifunctor . |
Relude.Extra.CallStack | Useful functions to extract information from CallStack . |
Relude.Extra.Enum | Extra utilities for types that implement Bounded
and Enum constraints. |
Relude.Extra.Foldable | Extra folds for instances of the Foldable typeclass.
Currently, just a short-circuitable left fold. |
Relude.Extra.Foldable1 | Foldable1 typeclass
like Foldable but for non-empty structures. |
Relude.Extra.Group | Grouping functions, polymorphic on return Map type. |
Relude.Extra.Lens | Minimal implementation of lens package required
for basic usage. |
Relude.Extra.Map | Typeclass for Map -like data structures. |
Relude.Extra.Newtype | Generic functions that automatically work for any
newtype . |
Relude.Extra.Tuple | Functions for working with tuples. |
Relude.Extra.Type | Functions for inspecting and working with types. |
Relude.Unsafe | Unsafe partial functions (produce error ) for lists and
Maybe . |