Difference between revisions of "The Other Prelude"

From HaskellWiki
Jump to navigation Jump to search
(String class?)
 
(24 intermediate revisions by 9 users not shown)
Line 1: Line 1:
  +
== Call For Contribution ==
[[Category:Proposals]]
 
   
== 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.
 
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 ==
 
== Committee ==
  +
This project has no committee whatsoever. Haskell community discussed the issues [[Talk:The Other Prelude|here]].
 
  +
This project has no committee whatsoever. Issues are discussed on [[Talk:The Other Prelude|the talk page]].
   
 
== Naming Conventions ==
 
== Naming Conventions ==
  +
 
* Function names should be easy for beginners to consume.
 
* Function names should be easy for beginners to consume.
 
* Specifically, ''The Other Prelude'' naming convention is to use
 
* Specifically, ''The Other Prelude'' naming convention is to use
Line 13: Line 14:
 
** whole English words and camelCase for functions (''e.g.'', <hask>orElse</hask> but not <hask>fmap</hask>)
 
** whole English words and camelCase for functions (''e.g.'', <hask>orElse</hask> but not <hask>fmap</hask>)
   
== The Hierarchy ==
+
== Design Philosophy ==
  +
Although, not Haskell 98, hierarchical modules will definitely be in Haskell'. We take it for granted.
 
  +
=== 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.
  +
* <hask>concat</hask> means the same thing as <hask>join</hask>. We propose we don't use <hask>concat</hask> at all.
  +
* <hask>concatMap</hask> is just <hask>(>>=)</hask>. 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.
 
* <hask>TheOtherPrelude</hask> - Minimalistic module.
 
* <hask>TheOtherPrelude</hask> - Minimalistic module.
* <hask>TheOtherPrelude.Extension</hask> - Convenient definitions.
+
* <hask>TheOtherPrelude.Utilities</hask> - Convenient definitions. The reasoning behind its existence is that we want the Prelude to be very concise. It should not steal good names.
  +
* <hask>TheOtherPrelude.Legacy</hask> - providing as much backwards compatibility as possible
   
 
== Open Issues ==
 
== Open Issues ==
  +
* Should Prelude functions use <hask>Integer</hask> instead of <hask>Int</hask>?
 
  +
* 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 <hask>Integer</hask> instead of <hask>Int</hask>? Maybe <hask>Integral n => n</hask> or <hask>Ix i => i</hask> in some cases?
 
* Should <hask>String</hask> be a class rather than a type synonym?
 
* Should <hask>String</hask> be a class rather than a type synonym?
  +
* The current proposal lacks a well thought <hask>fail</hask> mechanism. Should it be integrated into <hask>MonadZero</hask>, or have a class of his own, or remain in the <hask>Monad</hask> 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 ==
 
== 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.
 
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 imaginery Prelude as it stands,
+
The imaginary Prelude as it stands:
  +
  +
=== <hask>TheOtherPrelude.hs</hask> ===
   
 
<haskell>
 
<haskell>
  +
{-# LANGUAGE NoImplicitPrelude #-}
import Prelude () -- hide everything
 
   
  +
module TheOtherPrelude where
-- the idea is to remove 'fmap'.
 
  +
-- both map :: (a -> b) -> [a] -> [b] ('fmap' for the monad [])
 
  +
import Prelude (id, const, flip, (.))
-- and (.) :: (a -> b) -> (e -> a) -> (e -> b) ('fmap' for the (->) e monad)
 
  +
-- 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.
 
-- are good names, and are intuitively prefix and infix respectively.
  +
-- 'map' is aliased as (.) below.
  +
 
class Functor f where
 
class Functor f where
-- 'fmap' is guilty of nothing but a bad name
+
map :: (a -> b) -> f a -> f b
map, (.) :: (a -> b) -> f a -> f b
 
   
  +
-- definitely a bad idea, sorry Cale!
-- implementing either is enough
 
  +
-- (.) :: (Functor f) => (a -> b) -> f a -> f b
map = (.)
 
(.) = map
+
-- (.) = map
   
  +
class (Functor p) => Applicative p where
-- the following has been shamelessly copied,
 
  +
-- Minimal complete definition: return and (<@>).
-- from the [[Functor hierarchy proposal]] wiki page.
 
  +
pure :: a -> p a -- value lifting
class Functor f => Applicative f where
 
  +
-- actually I think we should
-- lifting a value
 
  +
-- stick to return
return :: a -> f a
 
  +
-- 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 = (<@>)
   
-- should this be named 'ap'? is 'ap' a good name?
 
-- can you come up with a better name?
 
-- can it refactor the liftM* type gymnastics?
 
(<*>) :: f (a -> b) -> f a -> f b
 
 
-- this leaves little left for the actual Monad class
 
 
class (Applicative m) => Monad m where
 
class (Applicative m) => Monad m where
-- the binding operation, gist of a monad
+
-- Minimal complete definition: one of join or (>>=).
(>>=) :: m a -> (a -> m b) -> m b
+
(>>=) :: m a -> (a -> m b) -> m b -- bind
  +
join :: m (m a) -> m a -- combining levels of structure
   
  +
ma >>= k = join (map k ma)
-- throwing out the outer monad
 
join :: m (m a) -> m a
+
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.
-- when the second is independent of the first
 
  +
-- 'zero' will be used when pattern matching against refutable patterns in
-- included in the class in case performance can be enhanced
 
  +
-- do-notation as well as to provide support for monad comprehensions.
(>>) :: m a -> m b -> m b
 
   
  +
class (Monad mz) => MonadZero mz where
-- intuitive definitions
 
  +
-- Should satisfy 'left zero': zero >>= f = zero
fa >> fb = (map (const id) fa) <*> fb -- is there a better definition?
 
  +
zero :: mz a
x >>= f = join (map f x)
 
join x = x >>= id
 
   
  +
class (MonadZero mp) => MonadPlus mp where
-- we shamelessly copy from the [[MonadPlus reform proposal]] now.
 
  +
-- 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
-- zero will be used when pattern matching against refutable patterns in
 
  +
-- Should satisfy 'monoid':
-- do-notation as well as to provide support for monad comprehensions.
 
  +
-- 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
-- should satisfy 'left zero': zero >>= f = zero
 
  +
fail :: String -> m a
class (Monad m) => MonadZero m where
 
  +
</haskell>
zero :: m a
 
   
  +
=== <hask>TheOtherPrelude/Utilities.hs</hask> ===
-- should satisfy 'monoid'
 
  +
-- zero ++ b = b, b ++ zero = b, (a ++ b) ++ c = a ++ (b ++ c)
 
  +
<haskell>
-- and 'left distribution'
 
  +
module TheOtherPrelude.Utilities where
-- (a ++ b) >>= f = (a >>= f) ++ (b >>= f)
 
  +
import Prelude () -- hide everything
class (MonadZero m) => MonadPlus m where
 
(++) :: m a -> m a -> m a
 
   
  +
-- this is the if-then-else proposal
-- should satisfy 'monoid'
 
  +
-- the name has been chosen to reflect the magic of Church booleans!
-- zero `orElse` b = b, b `orElse` zero = b
 
  +
-- the order of arguments matches that of maybe and either.
-- (a `orElse` b) `orElse` c = a `orElse` (b `orElse` c)
 
  +
boolean x _ True = x
-- and 'left catch'
 
  +
boolean _ y False = y
-- (return a) `orElse` b = a
 
class (MonadZero m) => MonadOr m where
 
orElse :: m a -> m a -> m a
 
 
</haskell>
 
</haskell>
   
 
== How To Use ==
 
== How To Use ==
  +
 
<haskell>
 
<haskell>
 
-- ''The Other Prelude'' is an alternative, not a replacement.
 
-- ''The Other Prelude'' is an alternative, not a replacement.
 
-- So we need to hide everything from the Prelude
 
-- So we need to hide everything from the Prelude
import Prelude ()
+
--import Prelude ()
  +
-- Now that we have it,
 
  +
{-# LANGUAGE NoImplicitPrelude #-}
 
-- This is just an example assuming there is nothing to hide
 
-- This is just an example assuming there is nothing to hide
import TheOtherPrelude
+
import TheOtherPrelude
   
 
-- Hopefully, this module will contain lift,...
 
-- Hopefully, this module will contain lift,...
 
-- Standard convention is to use M.lift (instead of liftM)
 
-- Standard convention is to use M.lift (instead of liftM)
import qualified TheOtherPrelude.Monad.Kleisli as M
+
-- import qualified TheOtherPrelude.Monad.Kleisli as M
 
</haskell>
 
</haskell>
   
 
== See also ==
 
== See also ==
  +
* [[Mathematical prelude discussion]] - A numeric Prelude in good shape already. Will a merger be ever possible?
 
  +
* [[Class system extension proposal]] - Makes this proposal worth reading at last
* [[Prelude extensions]] and [[Prelude function suggestions]] - Unlike ''The Other Prelude'' they ''enhance'' the Prelude.
 
  +
* [[Quantified contexts]] - Another important issue
 
* [[Functor hierarchy proposal]] - Making <hask>Monad m</hask> imply <hask>Functor m</hask> (adopted by ''The Other Prelude'').
 
* [[Functor hierarchy proposal]] - Making <hask>Monad m</hask> imply <hask>Functor m</hask> (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 <hask>if</hask> a function.
 
  +
* [[If-then-else]] - Making <hask>if</hask> a function (partially adopted by ''The Other Prelude'', we are silent on the bigger issue of sugar).
 
* [http://software.complete.org/missingh/static/doc/ MissingH] - Functions "missing" from the Haskell Prelude/libraries.
 
* [http://software.complete.org/missingh/static/doc/ MissingH] - Functions "missing" from the Haskell Prelude/libraries.
 
* [[MonadPlus reform proposal]] - Clarifies ambiguities around MonadPlus laws (adopted by ''The Other Prelude'')
 
* [[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.
  +
  +
[[Category:Proposals]]
 
[[Category:Mathematics]]
 
[[Category:Mathematics]]
 
[[Category:Code]]
 
[[Category:Code]]

Latest revision as of 22:37, 22 December 2010

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 not fmap)

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 as join. We propose we don't use concat 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 of Int? Maybe Integral n => n or Ix 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 into MonadZero, or have a class of his own, or remain in the Monad 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

{-# 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

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