The Other Prelude
Call For Contribution
This fun project, called The Other Prelude, is a creative reconstruction of the standard Prelude. By disregarding history and compatibility, we get a clean sheet.
Committee
This project has no committee whatsoever. Issues are discussed on the talk page.
Naming Conventions
- Function names should be easy for beginners to consume.
- Specifically, The Other Prelude naming convention is to use
- descriptive symbols for functions that are naturally infix (e.g.,
mplus
is replaced by(++)
) - whole English words and camelCase for functions (e.g.,
orElse
but notfmap
)
- descriptive symbols for functions that are naturally infix (e.g.,
Design Philosophy
Taking Typeclasses Seriously
Following Not just Maybe, functions should be generalized whenever possible. Of course, efficiency might be a concern but this is a fun project anyway.
concat
means the same thing asjoin
. We propose we don't useconcat
at all.concatMap
is just(>>=)
. That is, monadic functions are preferred over the same functions with different name.
The Hierarchy
Although, not Haskell98, hierarchical modules are already in Haskell2010. We take it for granted.
TheOtherPrelude
- Minimalistic module.TheOtherPrelude.Utilities
- Convenient definitions. The reasoning behind its existence is that we want the Prelude to be very concise. It should not steal good names.TheOtherPrelude.Legacy
- providing as much backwards compatibility as possible
Open Issues
- When the same function has an infix and a prefix implementation, should one of them be outside the class to enforce consistency?
- Should Prelude functions use
Integer
instead ofInt
? MaybeIntegral n => n
orIx i => i
in some cases? - Should
String
be a class rather than a type synonym? - The current proposal lacks a well thought
fail
mechanism. Should it be integrated intoMonadZero
, or have a class of his own, or remain in theMonad
class?
Reality
What we have here right now is not ready to be adopted by existing projects. The class system extension proposal might make a difference.
The Code
Currently, the code is in Wiki form. If people do agree that the collaborative decisions begot something pretty, we'll have a group of files in darcs.haskell.org some time.
The imaginary Prelude as it stands:
TheOtherPrelude.hs
TheOtherPrelude.hs
{-# LANGUAGE NoImplicitPrelude #-}
module TheOtherPrelude where
import Prelude (id, const, flip, (.))
-- hide almost everything
-- in fact, we could do better, by just defining them here
-- The idea is to rename 'fmap'.
-- Both map :: (a -> b) -> [a] -> [b] (in [])
-- and (.) :: (a -> b) -> (e -> a) -> (e -> b) (in (->) e)
-- are good names, and are intuitively prefix and infix respectively.
-- 'map' is aliased as (.) below.
class Functor f where
map :: (a -> b) -> f a -> f b
-- definitely a bad idea, sorry Cale!
-- (.) :: (Functor f) => (a -> b) -> f a -> f b
-- (.) = map
class (Functor p) => Applicative p where
-- Minimal complete definition: return and (<@>).
pure :: a -> p a -- value lifting
-- actually I think we should
-- stick to return
-- to make do notation work
(<@>) :: p (a -> b) -> p a -> p b -- lifted application
(>>) :: p a -> p b -> p b -- when the second is independent of the first
pa >> pb = (const id) . pa <@> pb
--map f pa = return f <@> pa -- see Class system extension proposal, below
apply :: (Applicative p) => p (a -> b) -> p a -> p b
apply = (<@>)
class (Applicative m) => Monad m where
-- Minimal complete definition: one of join or (>>=).
(>>=) :: m a -> (a -> m b) -> m b -- bind
join :: m (m a) -> m a -- combining levels of structure
ma >>= k = join (map k ma)
join mma = mma >>= id
--mf <@> ma = mf >>= flip map ma -- see Class system extension proposal, below
--ma >> mb = ma >>= const mb
--map f ma = ma >>= return . f -- this depends on (.), which is map! Be careful.
-- We copy from the MonadPlus reform proposal (link below) now.
-- 'zero' will be used when pattern matching against refutable patterns in
-- do-notation as well as to provide support for monad comprehensions.
class (Monad mz) => MonadZero mz where
-- Should satisfy 'left zero': zero >>= f = zero
zero :: mz a
class (MonadZero mp) => MonadPlus mp where
-- Should satisfy 'monoid':
-- zero ++ b = b; b ++ zero = b
-- (a ++ b) ++ c = a ++ (b ++ c)
-- and 'left distribution':
-- (a ++ b) >>= f = (a >>= f) ++ (b >>= f)
(++) :: mp a -> mp a -> mp a
class (MonadZero mo) => MonadOr mo where
-- Should satisfy 'monoid':
-- zero `orElse` b = b; b `orElse` zero = b
-- (a `orElse` b) `orElse` c = a `orElse` (b `orElse` c)
-- and 'left catch':
-- (return a) `orElse` b = a
orElse :: mo a -> mo a -> mo a
class (Monad m) => MonadFail m where
fail :: String -> m a
TheOtherPrelude/Utilities.hs
TheOtherPrelude/Utilities.hs
module TheOtherPrelude.Utilities where
import Prelude () -- hide everything
-- this is the if-then-else proposal
-- the name has been chosen to reflect the magic of Church booleans!
-- the order of arguments matches that of maybe and either.
boolean x _ True = x
boolean _ y False = y
How To Use
-- ''The Other Prelude'' is an alternative, not a replacement.
-- So we need to hide everything from the Prelude
--import Prelude ()
-- Now that we have it,
{-# LANGUAGE NoImplicitPrelude #-}
-- This is just an example assuming there is nothing to hide
import TheOtherPrelude
-- Hopefully, this module will contain lift,...
-- Standard convention is to use M.lift (instead of liftM)
-- import qualified TheOtherPrelude.Monad.Kleisli as M
See also
- Class system extension proposal - Makes this proposal worth reading at last
- Quantified contexts - Another important issue
- Functor hierarchy proposal - Making
Monad m
implyFunctor m
(adopted by The Other Prelude). - Functor-Applicative-Monad Proposal - in essence the same proposal, perhaps showing this sentiment is more common than assumed
- If-then-else - Making
if
a function (partially adopted by The Other Prelude, we are silent on the bigger issue of sugar). - MissingH - Functions "missing" from the Haskell Prelude/libraries.
- MonadPlus reform proposal - Clarifies ambiguities around MonadPlus laws (adopted by The Other Prelude)
- Mathematical prelude discussion - A Numeric Prelude in good shape already. Will a merger be ever possible?
- Prelude extensions and List function suggestions - Unlike The Other Prelude they enhance the Prelude.
- Not just Maybe - Instead of writing inside a specific monad (i.e. Maybe) write functions generalized on (Monad m)=> where possible.