universum-1.4.0: Custom prelude used in Serokell

Safe HaskellTrustworthy
LanguageHaskell2010

Universum

Contents

Description

Main module that reexports all functionality allowed to use without importing any other modules. Just add next lines to your module to replace default Prelude with better one.

{-# LANGUAGE NoImplicitPrelude #-}

import Universum

This documentation section contains description of internal module structure to help navigate between modules, search for interesting functionalities and understand where you need to put your new changes.

Functions and types are distributed across multiple modules and grouped by meaning or theme. Name of the module should give you hints regarding what this module contains. Some themes contain a great amount of both reexported functions and functions of our own. To make it easier to understand these huge chunks of functions, all reexported stuff is moved into separate module with name Universum.SomeTheme.Reexport and our own functions and types are in Universum.SomeTheme.SomeName. For example, see modules Universum.Container.Class and Universum.Container.Reexport.

Below is a short description of what you can find under different modules:

Synopsis

Reexports from base and from modules in this repo

Lenses

(&) :: a -> (a -> b) -> b infixl 1 #

& is a reverse application operator. This provides notational convenience. Its precedence is one higher than that of the forward application operator $, which allows & to be nested in $.

>>> 5 & (+1) & show
"6"

Since: base-4.8.0.0

(<&>) :: Functor f => f a -> (a -> b) -> f b infixl 1 #

Flipped version of <$>.

(<&>) = flip fmap

Examples

Expand

Apply (+1) to a list, a Just and a Right:

>>> Just 2 <&> (+1)
Just 3
>>> [1,2,3] <&> (+1)
[2,3,4]
>>> Right 3 <&> (+1)
Right 4

Since: base-4.11.0.0

(^?) :: s -> Getting (First a) s a -> Maybe a infixl 8 #

s ^? t returns the 1st element t returns, or Nothing if t doesn't return anything. It's trivially implemented by passing the First monoid to the getter.

Safe head:

>>> [] ^? each
Nothing
>>> [1..3] ^? each
Just 1

Converting Either to Maybe:

>>> Left 1 ^? _Right
Nothing
>>> Right 1 ^? _Right
Just 1

A non-operator version of (^?) is called preview, and – like view – it's a bit more general than (^?) (it works in MonadReader). If you need the general version, you can get it from microlens-mtl; otherwise there's preview available in Lens.Micro.Extras.

(^..) :: s -> Getting (Endo [a]) s a -> [a] infixl 8 #

s ^.. t returns the list of all values that t gets from s.

A Maybe contains either 0 or 1 values:

>>> Just 3 ^.. _Just
[3]

Gathering all values in a list of tuples:

>>> [(1,2),(3,4)] ^.. each.each
[1,2,3,4]

(^.) :: s -> Getting a s a -> a infixl 8 #

(^.) applies a getter to a value; in other words, it gets a value out of a structure using a getter (which can be a lens, traversal, fold, etc.).

Getting 1st field of a tuple:

(^. _1) :: (a, b) -> a
(^. _1) = fst

When (^.) is used with a traversal, it combines all results using the Monoid instance for the resulting type. For instance, for lists it would be simple concatenation:

>>> ("str","ing") ^. each
"string"

The reason for this is that traversals use Applicative, and the Applicative instance for Const uses monoid concatenation to combine “effects” of Const.

A non-operator version of (^.) is called view, and it's a bit more general than (^.) (it works in MonadReader). If you need the general version, you can get it from microlens-mtl; otherwise there's view available in Lens.Micro.Extras.

set :: ASetter s t a b -> b -> s -> t #

set is a synonym for (.~).

Setting the 1st component of a pair:

set _1 :: x -> (a, b) -> (x, b)
set _1 = \x t -> (x, snd t)

Using it to rewrite (<$):

set mapped :: Functor f => a -> f b -> f a
set mapped = (<$)

(.~) :: ASetter s t a b -> b -> s -> t infixr 4 #

(.~) assigns a value to the target. It's the same thing as using (%~) with const:

l .~ x = l %~ const x

See set if you want a non-operator synonym.

Here it is used to change 2 fields of a 3-tuple:

>>> (0,0,0) & _1 .~ 1 & _3 .~ 3
(1,0,3)

over :: ASetter s t a b -> (a -> b) -> s -> t #

over is a synonym for (%~).

Getting fmap in a roundabout way:

over mapped :: Functor f => (a -> b) -> f a -> f b
over mapped = fmap

Applying a function to both components of a pair:

over both :: (a -> b) -> (a, a) -> (b, b)
over both = \f t -> (f (fst t), f (snd t))

Using over _2 as a replacement for second:

>>> over _2 show (10,20)
(10,"20")

(%~) :: ASetter s t a b -> (a -> b) -> s -> t infixr 4 #

(%~) applies a function to the target; an alternative explanation is that it is an inverse of sets, which turns a setter into an ordinary function. mapped %~ reverse is the same thing as fmap reverse.

See over if you want a non-operator synonym.

Negating the 1st element of a pair:

>>> (1,2) & _1 %~ negate
(-1,2)

Turning all Lefts in a list to upper case:

>>> (mapped._Left.mapped %~ toUpper) [Left "foo", Right "bar"]
[Left "FOO",Right "bar"]

_1 :: Field1 s t a b => Lens s t a b #

Gives access to the 1st field of a tuple (up to 5-tuples).

Getting the 1st component:

>>> (1,2,3,4,5) ^. _1
1

Setting the 1st component:

>>> (1,2,3) & _1 .~ 10
(10,2,3)

Note that this lens is lazy, and can set fields even of undefined:

>>> set _1 10 undefined :: (Int, Int)
(10,*** Exception: Prelude.undefined

This is done to avoid violating a lens law stating that you can get back what you put:

>>> view _1 . set _1 10 $ (undefined :: (Int, Int))
10

The implementation (for 2-tuples) is:

_1 f t = (,) <$> f    (fst t)
             <*> pure (snd t)

or, alternatively,

_1 f ~(a,b) = (\a' -> (a',b)) <$> f a

(where ~ means a lazy pattern).

_2, _3, _4, and _5 are also available (see below).

_2 :: Field2 s t a b => Lens s t a b #

_3 :: Field3 s t a b => Lens s t a b #

_4 :: Field4 s t a b => Lens s t a b #

_5 :: Field5 s t a b => Lens s t a b #

type Lens s t a b = forall (f :: * -> *). Functor f => (a -> f b) -> s -> f t #

Lens s t a b is the lowest common denominator of a setter and a getter, something that has the power of both; it has a Functor constraint, and since both Const and Identity are functors, it can be used whenever a getter or a setter is needed.

  • a is the type of the value inside of structure
  • b is the type of the replaced value
  • s is the type of the whole structure
  • t is the type of the structure after replacing a in it with b

type Lens' s a = Lens s s a a #

This is a type alias for monomorphic lenses which don't change the type of the container (or of the value inside).

type Traversal s t a b = forall (f :: * -> *). Applicative f => (a -> f b) -> s -> f t #

Traversal s t a b is a generalisation of Lens which allows many targets (possibly 0). It's achieved by changing the constraint to Applicative instead of Functor – indeed, the point of Applicative is that you can combine effects, which is just what we need to have many targets.

Ultimately, traversals should follow 2 laws:

t pure ≡ pure
fmap (t f) . t g ≡ getCompose . t (Compose . fmap f . g)

The 1st law states that you can't change the shape of the structure or do anything funny with elements (traverse elements which aren't in the structure, create new elements out of thin air, etc.). The 2nd law states that you should be able to fuse 2 identical traversals into one. For a more detailed explanation of the laws, see this blog post (if you prefer rambling blog posts), or The Essence Of The Iterator Pattern (if you prefer papers).

Traversing any value twice is a violation of traversal laws. You can, however, traverse values in any order.

type Traversal' s a = Traversal s s a a #

This is a type alias for monomorphic traversals which don't change the type of the container (or of the values inside).

preuse :: MonadState s m => Getting (First a) s a -> m (Maybe a) #

preuse is (^?) (or preview) which implicitly operates on the state – it takes the state and applies a traversal (or fold) to it to extract the 1st element the traversal points at.

preuse l = gets (preview l)

use :: MonadState s m => Getting a s a -> m a #

use is (^.) (or view) which implicitly operates on the state; for instance, if your state is a record containing a field foo, you can write

x <- use foo

to extract foo from the state. In other words, use is the same as gets, but for getters instead of functions.

The implementation of use is straightforward:

use l = gets (view l)

If you need to extract something with a fold or traversal, you need preuse.

preview :: MonadReader s m => Getting (First a) s a -> m (Maybe a) #

preview is a synonym for (^?), generalised for MonadReader (just like view, which is a synonym for (^.)).

>>> preview each [1..5]
Just 1

view :: MonadReader s m => Getting a s a -> m a #

view is a synonym for (^.), generalised for MonadReader (we are able to use it instead of (^.) since functions are instances of the MonadReader class):

>>> view _1 (1, 2)
1

When you're using Reader for config and your config type has lenses generated for it, most of the time you'll be using view instead of asks:

doSomething :: (MonadReader Config m) => m Int
doSomething = do
  thingy        <- view setting1  -- same as “asks (^. setting1)”
  anotherThingy <- view setting2
  ...