hydrogen-prelude ================ + [`about`](#about) + [`scravy.de/hydrogen-prelude`](http://scravy.de/hydrogen-prelude) + [`hackage.haskell.org/package/hydrogen-prelude`](http://hackage.haskell.org/package/hydrogen-prelude) + [`goodies`](#goodies) + [`(!)`](#--has-a--a--haskey-a--hasvalue-a) + [`(?)`](#--container-a--a--contained-a--bool) + [`tmap`](#tmap) + [`fmap` vs `map`](#fmap-vs-map) + [`__`](#__--a) + [`|>`](#fsharps--which-is-flip-) + [`safeHead`](#safehead--a--a--a) + [`ShowBox`](#showbox--forall-a-show-a--a--showbox) + [`.|`, `.&`, `.^`](#----a--bool--a--bool--a--bool) + [`List a`](#type-list-a--a) + [`re-exports`](#re-exports) + [`Hydrogen.Prelude`](#hydrogenprelude) + [`Hydrogen.Prelude.IO`](#hydrogenpreludeio) + [`Hydrogen.Prelude.System`](#hydrogenpreludesystem) + [`Hydrogen.Prelude.Network`](#hydrogenpreludenetwork) + [`FAQ`](#faq) about ----- A Prelude that exports much of the standard library (more then `Prelude`), without conflicts. If for example you were to import `Prelude` and `Data.List` or `Data.Foldable` you will run into ambiguous imports (regarding `foldr` for example). This Prelude aims at exporting the most general functions (in this case `foldr` from `Data.Foldable`). It also pulls in some default packages like `cereal` for serialization and `containers` for data types like `Map` and `Set`. Every datatype exported by this Prelude comes with instances for `Serialize`. Longs story short, instead of: import Prelude hiding ( all, and, any, concat, concatMap, elem, foldl, foldl1, foldr, foldr1, mapM, mapM_, maximum, minimum, notElem, or, product, sequence, sequence_, sum ) import "base" Control.Monad hiding ( forM, forM_, mapM, mapM_, msum, sequence, sequence_ ) import Data.Foldable import Data.Traversable import Data.List hiding ( all, and, any, concat, concatMap, elem, find, foldl, foldl', foldl1, foldr, foldr1, mapAccumL, mapAccumR, maximum, maximumBy, minimum, minimumBy, notElem, or, product, sum ) it suffices to: import Hydrogen.Prelude goodies ------- Beyond existing functions from well-known standard packages, this prelude defines a few utilities (mostly aimed at unifying functionality across different packages, like `containers` and `array`). ### `(!) :: Has a ⇒ a → HasKey a → HasValue a` `(!)` is provided for several data types which associate a key and a value. [(1, 'a'), (3, 'v')] ! 1 → 'a' Instances are defined for + `Eq k ⇒ [(k, v)]` + `Ix i ⇒ Array i e` with `HasKey → i` + `Ord k ⇒ Map k v` with `HasValue → v` + `Ord k ⇒ MultiMap k v` with `HasValue → [v]` ### `(?) :: Container a ⇒ a → Contained a → Bool` Check whether the element on the right is contained in the collection on the left. [1, 2, 4] ? 3 → False Instances are defined for + `Eq a ⇒ [a]` + `Ord a ⇒ Set a` + `Eq a ⇒ Seq a` + `Ord k ⇒ Map k v` with `Contained → k` + `Ord k ⇒ MultiMap k v` with `Contained → k` ### `tmap` A little bit like `fmap` but defined differently on some datatypes (applies e.g. to both components of a tuple). tmap succ (3, 4) → (4, 5) Instances are defined for + `(a, a)` + `(a, a, a)` + `(a, a, a, a)` + `[a]` + `Seq a` + `Map k v` + `MultiMap k v` ### `fmap` vs `map` Hydrogen Prelude exports `fmap` as `map` - the way it ought to be. ### `__ :: a` A handy shortcut for `undefined`. ### FSharp's `|>` (which is `flip ($)`) Use it to pipe things from one function to the other, left to right: head xs |> fromEnum |> show ### `safeHead :: a → [a] → a` The head of the list, or the default given as first argument. safeHead x xs = maybe x head . listToMaybe ### `ShowBox :: forall a. (Show a) ⇒ a → ShowBox` ### Wrap anything that is showable (can be used to build heterogeneous lists). ### `.|, .&, .^ :: (a → Bool) → (a → Bool) → (a → Bool)` Combines predicates. filter (isDigit .| isLetter) ### `type List a = [a]` A shorthand for the type of lists, if you prefer this more wordy version. re-exports ---------- ### Hydrogen.Prelude The Hydrogen Prelude offers you the functions and datatypes from these modules, all with one import: + from [`base`](http://hackage.haskell.org/package/base) + `module Prelude` + `module Control.Applicative` + `module Control.Arrow` + `module Control.Monad` + `module Data.Bits` + `module Data.Bool` + `module Data.Char` + `module Data.Complex` + `module Data.Complex` + `module Data.Dynamic` + `module Data.Either` + `module Data.Fixed` + `module Data.Function` + `module Data.Foldable` + `module Data.Int` + `module Data.Ix` + `module Data.List` + `module Data.Maybe` + `module Data.Ord` + `module Data.Ratio` + `module Data.String` + `module Data.Time` + `module Data.Traversable` + `module Data.Tuple` + `module Data.Typeable` + `module Data.Word` + `module Numeric` + `module Text.Printf` + from [`array`](http://hackage.haskell.org/package/array) + `module Data.Array` + from [`cereal`](http://hackage.haskell.org/package/cereal) + `module Data.Serialize` + from [`containers`](http://hackage.haskell.org/package/containers) + `Data.Set`, `Data.Map`, and `Data.Seq` + from [`hashable`](http://hackage.haskell.org/package/hashable) + `module Data.Hashable` + form [`hydrogen-multimap`](http://hackage.haskell.org/package/hydrogen-multimap) + `Hydrogen.MultiMap` + from [`hydrogen-version`](http://hackage.haskell.org/package/hydrogen-version) + `module Hydrogen.Version` + from [`regex-tdfa`](http://hackage.haskell.org/package/regex-tdfa) + `module Text.Regex.TDFA` + from [`time`](http://hackage.haskell.org/package/time) + `module Data.Time` + from [`transformers`](http://hackage.haskell.org/package/transformers) + `module Data.Functor.Identity` + `module Data.Functor.Reverse` + from [`uuid`](http://hackage.haskell.org/package/uuid) + `Data.UUID` + `Data.UUID.fromString` as `uuidFromString` + `Data.UUID.V4.nextRandom` as `randomUUID` ### Hydrogen.Prelude.IO + from [`base`](http://hackage.haskell.org/package/base) + `module Data.IORef` + `module Control.Concurret` + `module Control.Exception` + `module System.IO` + `module System.Timeout` + from [`strict`](http://hackage.haskell.org/package/strict) + strict IO functions `hGetContents'`, `getContents'`, `readFile'`, `interact'` ### Hydrogen.Prelude.System + from [`base`](http://hackage.haskell.org/package/base) + `module System.CPUTime` + `module System.Environment` + `module System.Exit` + `module System.Info` + from [`directory`](http://hackage.haskell.org/package/directory) + `module System.Directory` + from [`filepath`](http://hackage.haskell.org/package/filepath) + `module System.FilePath` + from [`process`](http://hackage.haskell.org/package/process) + `module System.Process` + from [`random`](http://hackage.haskell.org/package/random) + `module System.Random` ### Hydrogen.Prelude.Network + from [`network`](http://hackage.haskell.org/package/network) + `module Network` FAQ === How is some of the *magic* accomplished? ---------------------------------------- Mostly with `XTypeFamilies` and `XStandaloneDeriving`. So this works only with GHC? ---------------------------- Yes, for now at least. What is `hydrogen` ------------------ https://www.youtube.com/watch?v=rbBX6aEzEz8