Copyright | (c) 2016 Stephen Diehl (c) 2016-2018 Serokell (c) 2018-2019 Kowainik |
---|---|
License | MIT |
Maintainer | Kowainik <xrom.xkov@gmail.com> |
Safe Haskell | Trustworthy |
Language | Haskell2010 |
The main module that reexports all functionality. It's considered to be a
Prelude
replacement.
One of the most convenient ways to use relude
is via mixins
feature. To use
this feature need to specify cabal-version: 2.4
in your package description.
And then you can add the following lines to the required stanza to replace
default Prelude with relude
.
mixins: base hiding (Prelude) , relude (Relude as Prelude)
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 Prelude:
module Prelude (module Relude) where import Relude
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
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.
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.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
andEnum
constraints. - Relude.Extra.Foldable: extra folds for instances of the
Foldable
typeclass. Currently, just a short-circuitable left fold. - Relude.Extra.Foldable1:
Foldable1
typeclass likeFoldable
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.Extra.Validation:
Validation
data type. - Relude.Unsafe: unsafe partial functions (produce
error
) for lists andMaybe
.
Synopsis
- module Relude.Applicative
- module Relude.Base
- module Relude.Bool
- module Relude.Container
- module Relude.Debug
- module Relude.DeepSeq
- 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
Modules available by default
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 lement 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.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 transormers 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.