Difference between revisions of "The Other Prelude"

From HaskellWiki
Jump to navigation Jump to search
m (added link to NotJustMaybe)
(class system extension proposal updates, and various other issues raised)
Line 19: Line 19:
   
 
== Open Issues ==
 
== Open Issues ==
  +
* 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?
 
* Should Prelude functions use <hask>Integer</hask> instead of <hask>Int</hask>?
 
* Should Prelude functions use <hask>Integer</hask> instead of <hask>Int</hask>?
 
* 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. May be the [[class system extension proposal]] can make a difference.
  +
   
 
== The Code ==
 
== The Code ==
Line 51: Line 58:
 
return :: a -> f a
 
return :: a -> f a
   
  +
-- lifted application, in prefix and infix form
-- should this be named 'ap'? is 'ap' a good name?
 
 
apply, (<*>) :: f (a -> b) -> f a -> f b
-- can you come up with a better name?
 
-- can it refactor the liftM* type gymnastics?
 
(<*>) :: f (a -> b) -> f a -> f b
 
 
 
 
-- when the second is independent of the first
 
-- when the second is independent of the first
 
(>>) :: m a -> m b -> m b
 
(>>) :: m a -> m b -> m b
  +
  +
  +
-- implementing either is enough
  +
apply = (<*>)
  +
(<*>) = apply
   
 
-- is there a better definition?
 
-- is there a better definition?
fa >> fb = (map (const id) fa) <*> fb
+
f >> g = (map (const id) f) <*> g
   
   
Line 104: Line 114:
   
 
[1]: [[Functor hierarchy proposal]]<br />
 
[1]: [[Functor hierarchy proposal]]<br />
[2]: [[MonadPlus reform proposal]]
+
[2]: [[MonadPlus reform proposal]]<br />
  +
[3]: [[Class system extension proposal]]
   
 
=== <hask>TheOtherPrelude.Utilities</hask> ===
 
=== <hask>TheOtherPrelude.Utilities</hask> ===
Line 133: Line 144:
   
 
== See also ==
 
== See also ==
  +
* [[Class system extension proposal]] - Makes this proposal worth reading at last
* [[Mathematical prelude discussion]] - A numeric Prelude in good shape already. Will a merger be ever possible?
 
* [[Prelude extensions]] and [[Prelude function suggestions]] - Unlike ''The Other Prelude'' they ''enhance'' the Prelude.
 
 
* [[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'').
 
* [[If-then-else]] - Making <hask>if</hask> a function (partially adopted by ''The Other Prelude'', we are silent on the bigger issue of sugar).
 
* [[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 [[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:Mathematics]]
 
[[Category:Mathematics]]

Revision as of 00:48, 11 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. Haskell community discussed the issues here.

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 imaginery Prelude as it stands,

TheOtherPrelude

-- module: TheOtherPrelude
import Prelude ()    -- hide everything


-- the idea is to remove 'fmap'.
-- both map :: (a -> b) -> [a] -> [b] ('fmap' for the monad []) 
-- and (.) :: (a -> b) -> (e -> a) -> (e -> b) ('fmap' for the (->) e monad)
-- are good names, and are intuitively prefix and infix respectively.
class Functor f where
  -- 'fmap' is guilty of nothing but a bad name
  map, (.) :: (a -> b) -> f a -> f b

  -- implementing either is enough
  map = (.)
  (.) = map


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


-- this leaves little left for the actual Monad class
class Applicative m => Monad m where
  -- the binding operation, gist of a monad 
  (>>=) :: m a -> (a -> m b) -> m b

  -- throwing out the outer monad
  join :: m (m a) -> m a

  -- intuitive definitions
  x >>= f = join (map f x)
  join x = x >>= id


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

-- should satisfy 'left zero': zero >>= f = zero
class Monad m => MonadZero m where
  zero :: m 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
-- (a `orElse` b) `orElse` c = a `orElse` (b `orElse` c)
-- and 'left catch'
-- (return a) `orElse` b = a
class MonadZero m => MonadOr m where
  orElse :: m a -> m a -> m a

[1]: Functor hierarchy proposal
[2]: MonadPlus reform proposal
[3]: Class system extension proposal

TheOtherPrelude.Utilities

-- module: TheOtherPrelude.Utilities

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