Difference between revisions of "The Other Prelude"

From HaskellWiki
Jump to navigation Jump to search
(Formatting, small code changes, moved method synonyms outside classes to enforce consistency (choices were arbitrary, change if you want))
Line 1: Line 1:
[[Category:Proposals]]
 
 
 
== Call For Contribution ==
 
== 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 14: Line 15:
   
 
== The Hierarchy ==
 
== The Hierarchy ==
  +
 
Although, not Haskell 98, hierarchical modules will definitely be in Haskell'. We take it for granted.
 
Although, not Haskell 98, hierarchical modules will definitely be in Haskell'. We take it for granted.
 
* <hask>TheOtherPrelude</hask> - Minimalistic module.
 
* <hask>TheOtherPrelude</hask> - Minimalistic module.
Line 19: Line 21:
   
 
== Open Issues ==
 
== Open Issues ==
  +
 
* Should <hask>Functor</hask> imply <hask>Monad</hask> or the other way around?
 
* Should <hask>Functor</hask> imply <hask>Monad</hask> or the other way around?
 
* When the same function has an infix and a prefix implementation, should one of them be outside the class to enforce consistency?
 
* When the same function has an infix and a prefix implementation, should one of them be outside the class to enforce consistency?
Line 26: Line 29:
   
 
== Reality ==
 
== Reality ==
  +
 
What we have here right now is not ready to be adopted by existing projects. May be the [[class system extension proposal]] can make a difference.
 
What we have here right now is not ready to be adopted by existing projects. May be the [[class system extension proposal]] can 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</hask> ===
 
  +
=== <hask>TheOtherPrelude.hs</hask> ===
  +
 
<haskell>
 
<haskell>
-- module: TheOtherPrelude
+
module TheOtherPrelude where
import Prelude () -- hide everything
 
   
  +
import Prelude () -- hide everything
   
-- the idea is to remove 'fmap'.
+
-- The idea is to rename 'fmap'.
-- both map :: (a -> b) -> [a] -> [b] ('fmap' for the monad [])
+
-- Both map :: (a -> b) -> [a] -> [b] (in [])
-- and (.) :: (a -> b) -> (e -> a) -> (e -> b) ('fmap' for the (->) e monad)
+
-- 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.
 
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
 
   
  +
(.) = map -- defined outside the class as an infix synonym for map.
-- implementing either is enough
 
map = (.)
 
(.) = map
 
   
  +
-- The following has been shamelessly copied from the
  +
-- Functor hierarchy proposal page (see links below).
  +
class (Functor p) => Applicative p where
  +
-- Minimal complete definition: return and (<*>).
  +
return :: a -> p a -- value lifting
  +
(<*>) :: p (a -> b) -> p a -> p b -- lifted application
  +
(>>) :: p a -> p b -> p b -- when the second is independent of the first
   
  +
-- Default definition:
-- the following has been shamelessly copied,
 
-- from the Functor hierarchy proposal[1] wiki page.
 
class Functor f => Applicative f where
 
-- lifting a value
 
return :: a -> f a
 
 
-- lifted application, in prefix and infix form
 
apply, (<*>) :: f (a -> b) -> f a -> f b
 
 
-- when the second is independent of the first
 
(>>) :: m a -> m b -> m b
 
 
 
-- implementing either is enough
 
apply = (<*>)
 
(<*>) = apply
 
 
-- is there a better definition?
 
 
f >> g = (map (const id) f) <*> g
 
f >> g = (map (const id) f) <*> g
   
  +
apply = (<*>) -- defined outside the class as a prefix synonym for (<*>).
   
  +
class (Applicative m) => Monad m where
-- this leaves little left for the actual Monad class
 
  +
-- Minimal complete definition: one of join or (>>=).
class Applicative m => Monad m where
 
 
(>>=) :: m a -> (a -> m b) -> m b -- bind
 
(>>=) :: m a -> (a -> m b) -> m b -- bind
join :: m (m a) -> m a -- combining levels of structure
+
join :: m (m a) -> m a -- combining levels of structure
   
-- Minimal complete instance: one of join or (>>=).
 
 
-- Default definitions:
 
-- Default definitions:
 
x >>= f = join (map f x)
 
x >>= f = join (map f x)
 
join x = x >>= id
 
join x = x >>= id
   
  +
-- We shamelessly copy from the MonadPlus reform proposal (link below) now.
 
  +
-- 'zero' will be used when pattern matching against refutable patterns in
-- we shamelessly copy from the MonadPlus reform proposal[2] now.
 
 
-- zero will be used when pattern matching against refutable patterns in
 
 
-- do-notation as well as to provide support for monad comprehensions.
 
-- do-notation as well as to provide support for monad comprehensions.
  +
-- Should satisfy 'left zero': zero >>= f = zero
  +
class (Monad mz) => MonadZero mz where
  +
zero :: mz a
   
-- should satisfy 'left zero': zero >>= f = zero
+
-- Should satisfy 'monoid':
  +
-- zero ++ b = b; b ++ zero = b; (a ++ b) ++ c = a ++ (b ++ c)
class Monad m => MonadZero m where
 
  +
-- and 'left distribution':
zero :: m a
 
  +
-- (a ++ b) >>= f = (a >>= f) ++ (b >>= f)
 
  +
class (MonadZero mp) => MonadPlus mp where
 
  +
(++) :: mp a -> mp a -> mp a
-- 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)
 
class MonadZero m => MonadPlus m where
 
(++) :: m a -> m a -> m a
 
   
  +
-- Should satisfy 'monoid':
 
  +
-- zero `orElse` b = b; b `orElse` zero = b
-- should satisfy 'monoid'
 
-- zero `orElse` b = b, b `orElse` zero = b
+
-- (a `orElse` b) `orElse` c = a `orElse` (b `orElse` c)
  +
-- and 'left catch':
-- (a `orElse` b) `orElse` c = a `orElse` (b `orElse` c)
 
  +
-- (return a) `orElse` b = a
-- and 'left catch'
 
  +
class (MonadZero mo) => MonadOr mo where
-- (return a) `orElse` b = a
 
  +
orElse :: mo a -> mo a -> mo a
class MonadZero m => MonadOr m where
 
orElse :: m a -> m a -> m a
 
 
</haskell>
 
</haskell>
   
  +
=== <hask>TheOtherPrelude/Utilities.hs</hask> ===
[1]: [[Functor hierarchy proposal]]<br />
 
[2]: [[MonadPlus reform proposal]]<br />
 
[3]: [[Class system extension proposal]]
 
   
=== <hask>TheOtherPrelude.Utilities</hask> ===
 
 
<haskell>
 
<haskell>
-- module: TheOtherPrelude.Utilities
+
module TheOtherPrelude.Utilities where
 
 
import Prelude () -- hide everything
 
import Prelude () -- hide everything
   
Line 125: Line 109:
 
boolean True x _ = x
 
boolean True x _ = x
 
boolean False _ y = y
 
boolean False _ y = y
 
 
</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 ()
   
 
-- 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 ==
  +
 
* [[Class system extension proposal]] - Makes this proposal worth reading at last
 
* [[Class system extension proposal]] - Makes this proposal worth reading at last
 
* [[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'').
Line 150: Line 136:
 
* [[Prelude extensions]] and [[Prelude function suggestions]] - Unlike ''The Other Prelude'' they ''enhance'' the Prelude.
 
* [[Prelude extensions]] and [[Prelude function suggestions]] - Unlike ''The Other Prelude'' they ''enhance'' the Prelude.
 
* [http://haskell.org/hawiki/NotJustMaybe NotJustMaybe] - Instead of writing inside a specific monad (i.e. Maybe) write functions generalized on (Monad m)=> where possible.
 
* [http://haskell.org/hawiki/NotJustMaybe NotJustMaybe] - 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]]

Revision as of 23:49, 19 January 2007

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)

The Hierarchy

Although, not Haskell 98, hierarchical modules will definitely be in Haskell'. 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.

Open Issues

  • Should Functor imply Monad or the other way around?
  • 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?
  • 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. May be the class system extension proposal can 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

module TheOtherPrelude where

import Prelude () -- hide everything

  -- 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.
class Functor f where
  map :: (a -> b) -> f a -> f b

(.) = map -- defined outside the class as an infix synonym for map.

-- The following has been shamelessly copied from the
-- Functor hierarchy proposal page (see links below).
class (Functor p) => Applicative p where
  -- Minimal complete definition: return and (<*>).
  return :: a -> p a                 -- value lifting
  (<*>)  :: p (a -> b) -> p a -> p b -- lifted application
  (>>)   :: p a -> p b -> p b        -- when the second is independent of the first

  -- Default definition:
  f >> g = (map (const id) f) <*> g

apply = (<*>) -- defined outside the class as a prefix synonym for (<*>).

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

  -- Default definitions:
  x >>= f = join (map f x)
  join x = x >>= id

-- We shamelessly 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.
-- Should satisfy 'left zero': zero >>= f = zero
class (Monad mz) => MonadZero mz where
  zero :: mz a

-- 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)
class (MonadZero mp) => MonadPlus mp where
  (++) :: mp a -> mp a -> mp a

-- 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
class (MonadZero mo) => MonadOr mo where
  orElse :: mo a -> mo a -> mo 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!
boolean True  x _ = x
boolean False _ y = y

How To Use

-- ''The Other Prelude'' is an alternative, not a replacement.
-- So we need to hide everything from the Prelude
import Prelude ()

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