Universum
universum
is a custom prelude used in @Serokell that has:
- Excellent documentation: tutorial, migration guide from
Prelude
,
Haddock with examples for (almost) every function,
all examples are tested with doctest
,
documenation regarding internal module structure.
universum
-specific HLint rules:
.hlint.yaml
- Only a few LiquidHaskell properties right now, but LiquidHaskell is on Travis
CI and other properties are just waiting to be added!
- Focus on safety, convenience and efficiency.
What is this file about?
This README contains introduction to Universum
and a tutorial on how to use it.
Structure of this tutorial
This tutorial has several parts:
- Philosophy and motivation.
- How to use
universum
.
- Changes in
Prelude
(some gotchas).
- Already known things that weren't in
Prelude
brought into scope.
- New things added.
- Migration guide from
Prelude
.
This is neither a tutorial on Haskell nor tutorial on each function contained in Universum. For detailed
documentation of every function together with examples and usage, see
Haddock documentation.
Why another custom Prelude? ↑
Motivation
At Serokell, we strive to be as productive as possible. That's why we are using Haskell. This choice of language implies
that we're restricted to use Prelude
:
implicit import of basic functions, type classes and data types. Unfortunately, the default Prelude
is considered to be not so good
due to some historical reasons.
This is why we decided to use a better tool. Luckily, Haskell provides us with the ability
to replace default Prelude
with an alternative. All we had to do is to implement a
new basic set of defaults. There already were plenty of preludes,
so we didn't plan to implement everything from scratch.
After some long, hot discussions, our team decided to base our custom prelude on
protolude
. If you're not familiar with it,
you can read a tutorial about protolude
.
The next section explains why we've made this choice and what we are willing to do.
This tutorial doesn't cover the differences from protolude
. Instead, it explains how Universum is different from regular Prelude
.
Main goals
While creating and maintaining a custom prelude, we are pursuing the following goals:
- Avoid all partial functions.
We like total and exception-free functions.
You can still use some unsafe functions from
Universum.Unsafe
module,
but they are not exported by default.
- Use more efficient string representations.
String
type is crushingly inefficient. All our functions either try to be polymorphic over string
type or use Text
as the default string type. Because the community is evolving slowly, some libraries still use String
type, so String
type alias is still reexported. We recommend to avoid String
as much as you can!
- Try to not reinvent the wheel. We're not trying to rebuild whole type hierarchy from scratch,
as it's done in
classy-prelude
.
Instead, we reexport common and well-known things from base
and some other
libraries that are used in everyday production programming in Haskell.
Note: well, we did end up inventing some new things.
- Export more useful and commonly used functions. Hello, my name is Dmitry. I was
coding Haskell for 3 years but still hoogling which module
liftIO
comes from.
Things like liftIO
, ReaderT
type, MVar
-related functions have unambiguous names,
are used in almost every non-trivial project, and it's really tedious to import them
manually every time.
Unlike protolude
, we are:
- Not trying to be as general as possible (thus we don't export much from
GHC.Generics
).
- Not trying to maintain every version of
ghc
compiler (only the
latest 3
- Trying to make writing production code easier (see
enhancements and fixes).
How to use Universum ↑
Okay, enough philosophy. If you want to just start using universum
and
explore it with the help of compiler, set everything up according to the instructions below.
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 Universum
If you're using Emacs and don't want to
type import Universum
manually every time, you can
modify your configs
a little bit.
If you want to get familiar with universum
internal structure, you can just
read top-level documentation for
Universum
module.
Gotchas ↑
head
, tail
, last
, init
work with NonEmpty a
instead of [a]
.
- Safe analogue for
head
function: safeHead :: [a] -> Maybe a
.
undefined
triggers a compiler warning, which is probably not what you want. Either use throwIO
, Except
, error
or bug
.
map
is fmap
now.
- 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 can't write Show
instances easily.
- You can't call some
Foldable
methods over Maybe
and some other types.
Foldable
generalization is useful but
potentially error-prone.
Instead we created our own fully compatible with Foldable
Container
type class
but that restricts the usage of functions like length
over Maybe
, Either
, Identity
and tuples.
We're also using GHC 8 feature of
custom compile-time errors
to produce
more helpful messages.
- As a consequence of previous point, some functions like
traverse_
, forM_
, sequenceA_
, etc.
are generalized over Container
type classes.
error
takes Text
.
Things that you were already using, but now you don't have to import them explicitly ↑
Commonly used libraries
First of all, we reexport some generally useful modules: Control.Applicative
,
Data.Traversable
, Data.Monoid
, Control.DeepSeq
, Data.List
, and lots of others.
Just remove unneeded imports after importing Universum
(GHC should tell you which ones).
Then, some commonly used types: Map/HashMap/IntMap
, Set/HashSet/IntSet
, Seq
, Text
and ByteString
(as well as synonyms LText
and LByteString
for lazy versions).
liftIO
and MonadIO
are exported by default. A lot of IO
functions are generalized to MonadIO
.
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
.
We also reexport big chunks of these libraries: mtl
, stm
, microlens
, microlens-mtl
.
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.
Text
We export Text
and LText
, 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.
Debugging and undefined
s
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).
Exceptions
We use safe-exceptions
library for exceptions handling. Don't import Control.Exceptions
module explicitly. Instead use functionality from safe-exceptions
provided by universum
or import Control.Exceptions.Safe
module.
What's new? ↑
Finally, we can move to part describing the new cool features we bring with universum
.
-
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")
).
-
Very generalized version of concatMapM
, too, is available and does what expected.
-
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 -> ... x ...
After:
whenJust mbX $ \x ->
... 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
.
-
Type operator $
for writing types like Maybe $ Either String $ Maybe Int
.
-
Each
type family. So this:
f :: Each [Show, Read] [a, b] => a -> b -> String
translates into this:
f :: (Show a, Show b, Read a, Read b) => a -> b -> String
-
With
type operator. So this:
a :: With [Show, Read] a => a -> a
translates into this:
a :: (Show a, Read a) => a -> a
-
Variadic composition operator (...)
. So you can write:
ghci> (show ... (+)) 1 2
"3"
ghci> show ... 5
"5"
ghci> (null ... zip5) [1] [2] [3] [] [5]
True
ghci> let process = map (+3) ... filter
ghci> process even [1..5]
[5,7]
-
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
.
-
ToPairs
type class for data types that can be converted to list of pairs (like Map
or HashMap
or IntMap
).
Migration guide from Prelude ↑
In order to replace default Prelude
with universum
you should start with instructions given in
how to use universum section.
This section describes what you need to change to make your code compile with universum
.
-
Enable -XOverloadedStrings
and -XTypeFamilies
extension by default for your project.
-
Since head
, tail
, last
and init
work for NonEmpty
you should
refactor your code in one of the multiple ways described below:
- Change
[a]
to NonEmpty a
where it makes sense.
- Use functions which return
Maybe
. They can be implemented using nonEmpty
function. Like head <$> nonEmpty l
.
head <$> nonEmpty l
is safeHead l
tail
is drop 1
. It's almost never a good idea to use tail
from Prelude
.
- Add
import qualified Universum.Unsafe as Unsafe
and replace function with qualified usage.
-
If you use fromJust
or !!
you should use them from import qualified Universum.Unsafe as Unsafe
.
-
Derive or implement Container
instances for your data types which implement
Foldable
instances. This can be done in a single line because Container
type class automatically derives from Foldable
.
-
Container
type class from universum
replaces Foldable
and doesn't have
instances for Maybe a
, (a, b)
, Identity a
and Either a b
. If you use
foldr
or forM_
or similar for something like Maybe a
you should 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 ()
-
If you have types like foo :: Foldable f => f a -> a -> a
you should chose one of the following:
Right
: Modify types for Container
like foo :: (Container t, Element t ~ a) => t -> a -> a
.
Left
: Import Data.Foldable
module qualified
and use everything Foldable
-related qualified.
-
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
.
-
Run hlint
using .hlint.yaml
file from universum
package to cleanup code and imports.
Projects that use Universum ↑