universum: Custom prelude used in Serokell

[ library, mit, prelude ] [ Propose Tags ]
Versions [RSS] 0.1.8, 0.1.12, 0.2, 0.2.1, 0.2.2, 0.3, 0.4, 0.4.1, 0.4.2, 0.4.3, 0.5, 0.5.1, 0.5.1.1, 0.6.0.0, 0.6.1, 0.7.0, 0.7.1, 0.7.1.1, 0.8.0, 0.9.0, 0.9.1, 0.9.2, 1.0.0, 1.0.1, 1.0.2, 1.0.3, 1.0.4, 1.0.4.1, 1.1.0, 1.1.1, 1.2.0, 1.3.0, 1.4.0, 1.5.0, 1.6.0, 1.6.1, 1.7.0, 1.7.1, 1.7.2, 1.7.3, 1.8.0, 1.8.1, 1.8.1.1, 1.8.2, 1.8.2.1 (info)
Change log CHANGES.md
Dependencies base (>=4.8 && <5), bytestring (>=0.10.8.1), containers (>=0.5.7.1), deepseq (>=1.4.2.0), ghc-prim (>=0.4.0.0), hashable (>=1.2.6.1), microlens (>=0.4.8.1), microlens-mtl (>=0.1.11.0), mtl (>=2.2.1), safe-exceptions (>=0.1.6.0), stm (>=2.4.4.1), text (>=1.2.2.2), text-format (>=0.3.1.1), transformers (>=0.5.2.0), type-operators (>=0.1.0.4), unordered-containers (>=0.2.8.0), utf8-string (>=1.0.1.1), vector (>=0.12.0.1) [details]
License MIT
Copyright 2016 Stephen Diehl, 2016-2018 Serokell
Author Stephen Diehl, @serokell
Maintainer Serokell <hi@serokell.io>
Category Prelude
Home page https://github.com/serokell/universum
Bug tracker https://github.com/serokell/universum/issues
Source repo head: git clone git@github.com:serokell/universum.git
Uploaded by shersh at 2018-02-21T13:56:38Z
Distributions LTSHaskell:1.8.2.1, NixOS:1.8.2.1, Stackage:1.8.2.1
Reverse Dependencies 23 direct, 8 indirect [details]
Downloads 23170 total (188 in the last 30 days)
Rating 1.75 (votes: 2) [estimated by Bayesian average]
Your Rating
  • λ
  • λ
  • λ
Status Docs available [build log]
Last success reported on 2018-02-21 [all 1 reports]

Readme for universum-1.1.0

[back to package description]

Universum

Build Status Windows build status Hackage Stackage LTS Stackage Nightly License: MIT

A custom prelude used in Serokell.

What is this?

This README contains introduction to Universum and a tutorial on how to use it.

Structure of this tutorial

This tutorial has several parts:

  1. Philosophy and motivation.
  2. How to use universum.
  3. Changes in Prelude (some gotchas).
  4. Already known things that weren't in Prelude brought into scope.
  5. New things added.

This is not a tutorial on Haskell, and not even a tutorial on each function. For the detailed documentation of every function with examples and usages see Haddock documentation.

Why another custom Prelude?

Motivation

In Serokell, we want to be as much 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. But 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. Hopefully Haskell provides us with ability to replace default Prelude with some alternative. All we need to do is to implement new basic set of defaults. But we don't intend to implement everything from scratch. There're already plenty of preludes. After some hot long 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 have 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 custom Prelude.

Main goals

While creating and maintaining a custom prelude, we are pursuing the following goals:

  1. Avoid all partial functions. We like total and exception-free functions. Though you can still use some unsafe functions from Universum.Unsafe module but they are not exported by default.
  2. Use more efficient string representations. String type is crushingly inefficient. All our functions either try to be polymorphic over string types, or use Text as the default string type. String type alias is still reexported, because the community is evolving slowly, some libraries still use String type. But we recommend to avoid String!
  3. Don't 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 used in everyday production programming in Haskell.

    Note: well, we did end up inventing something new.

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

  1. Not trying to be as general as possible (thus we don't export much from GHC.Generics).
  2. Not trying to maintain every version of ghc compiler (only the latest 3
  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, you can modify your configs a little bit if you don't want to type import Universum manually every time.

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. Either use autoderived instances or Buildable.
  • 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 undefineds

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.

  • pretty and prettyL for converting Buildable into Text (suggested be used instead of show).

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

Projects that use Universum

License

Released under the MIT License. Copyright (c) 2016, Stephen Diehl, 2016-2017, Serokell