Difference between revisions of "The Other Prelude"

From HaskellWiki
Jump to navigation Jump to search
m (combined Functor (.) and map type decls)
(prettifying)
Line 1: Line 1:
 
[[Category:Proposals]]
 
[[Category:Proposals]]
   
== Call for contribution ==
+
== Call For Contribution ==
This fun project, called "The Other Prelude", and 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.
   
== Naming conventions ==
+
== Committee ==
  +
This project has no committee whatsoever. Haskell community discussed the issues [[Talk:The Other Prelude|here]].
The principal is to make the names very readable for both beginners and category theorists (if any).
 
   
== Guidelines ==
+
== Naming Conventions ==
  +
* Function names should be easy for beginners to consume.
* The prelude should not contain any "projection" functions (like <hask>fst</hask> and <hask>snd</hask>. They go to the Extension module.
 
  +
* Specifically, ''The Other Prelude'' naming convention is to use
  +
** descriptive symbols for functions that are naturally infix (''e.g.'', <hask>mplus</hask> is replaced by <hask>(++)</hask>)
  +
** whole English words and camelCase for functions (''e.g.'', <hask>orElse</hask> but not <hask>fmap</hask>)
   
 
== The Hierarchy ==
 
  +
Although, not Haskell 98, hierarchical modules will definitely be in Haskell'. We take it for granted.
== Issues ==
 
* Should alphanumeric names be preferred over symbols when defining a class?
 
* Why do many functions in Prelude use <hask>Int</hask> instead of <hask>Integer</hask>? IMO, <hask>Integer</hask> should be THE preferred datatype for everything (examples: length, splitAt, replicate, drop, take, ...)!
 
 
 
== The hierarchy ==
 
 
* <hask>TheOtherPrelude</hask> - Minimalistic module.
 
* <hask>TheOtherPrelude</hask> - Minimalistic module.
 
* <hask>TheOtherPrelude.Extension</hask> - Convenient definitions.
 
* <hask>TheOtherPrelude.Extension</hask> - Convenient definitions.
   
== The code ==
+
== Open Issues ==
  +
* Should Prelude functions use <hask>Integer</hask> instead of <hask>Int</hask>?
  +
 
== 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.
   
Line 28: Line 29:
 
import Prelude () -- hide everything
 
import Prelude () -- hide everything
   
-- the idea is to remove 'fmap'
+
-- the idea is to remove 'fmap'.
-- and map :: (a -> b) -> [a] -> [b] to be a special case
+
-- both map :: (a -> b) -> [a] -> [b] ('fmap' for the monad [])
-- as well as having (.) :: (a -> b) -> (e -> a) -> (e -> b) as a
+
-- and (.) :: (a -> b) -> (e -> a) -> (e -> b) ('fmap' for the (->) e monad)
  +
-- are good names, and are intuitively prefix and infix respectively.
-- special case from the Functor instance for ((->) e)
 
-- Both notations can be provided to allow for clarity in different situations.
 
 
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
  +
  +
-- implementing either is enough
 
map = (.)
 
map = (.)
 
(.) = map
 
(.) = map
   
-- the following has been shamelessly copied
+
-- the following has been shamelessly copied,
-- from the functor hierarchy proposal wiki page
+
-- from the [[Functor hierarchy proposal]] wiki page.
 
class Functor f => Applicative f where
 
class Functor f => Applicative f where
  +
-- lifting a value
 
return :: a -> f a
 
return :: a -> f a
(<*>) :: f (a -> b) -> f a -> f b -- or should this be named 'ap'?
 
-- or something even better?
 
-- could this nice looking function
 
-- refactor the liftM* idioms?
 
 
(>>) :: f a -> f b -> f b
 
fa >> fb = (map (const id) fa) <*> fb
 
   
  +
-- 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
 
-- 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
 
(>>=) :: m a -> (a -> m b) -> m b
 
(>>=) :: m a -> (a -> m b) -> m b
  +
  +
-- throwing out the outer monad
 
join :: m (m a) -> m a
 
join :: m (m a) -> m a
  +
 
  +
-- when the second is independent of the first
  +
-- included in the class in case performance can be enhanced
 
(>>) :: m a -> m b -> m b
  +
  +
-- intuitive definitions
 
fa >> fb = (map (const id) fa) <*> fb -- is there a better definition?
 
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'' now.
-- end of Functor hierarchy dilemma
 
   
  +
-- should satisfy 'left zero': zero >>= f = zero
 
-- zero will be used when pattern matching against refutable patterns in
 
-- 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.
Line 65: Line 77:
 
zero :: m a
 
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
 
class (MonadZero m) => MonadPlus m where
 
(++) :: m a -> m a -> m a
 
(++) :: 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
 
class (MonadZero m) => MonadOr m where
 
orElse :: m a -> m a -> m a
 
orElse :: m a -> m a -> m a
 
 
</haskell>
 
</haskell>
   
  +
== How To Use ==
How to use it, as it stands,
 
 
 
<haskell>
 
<haskell>
  +
-- ''The Other Prelude'' is an alternative, not a replacement.
import Prelude () -- hide everything
 
  +
-- So we need to hide everything from the Prelude
import TheOtherPrelude -- get everything
 
 
import Prelude ()
import qualified TheOtherPrelude.Monad.Kleisli as M -- standard convention
 
  +
  +
-- 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
 
</haskell>
 
</haskell>
   
 
== See also ==
 
== See also ==
* [[Mathematical prelude discussion]] - A numeric Prelude. Could this be merged into this one?
+
* [[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.
+
* [[Prelude extensions]] and [[Prelude function suggestions]] - Unlike ''The Other Prelude'' they ''enhance'' the Prelude.
* [[Functor hierarchy proposal]] - making "Monad m" imply "Functor m"
+
* [[Functor hierarchy proposal]] - Making <hask>Monad m</hask> imply <hask>Functor m</hask> (adopted by ''The Other Prelude'').
* [[If-then-else]] - making "if" a function
+
* [[If-then-else]] - Making <hask>if</hask> a function.
* [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'')
 
 
[[Category:Mathematics]]
 
[[Category:Mathematics]]
 
[[Category:Code]]
 
[[Category:Code]]

Revision as of 13:34, 28 December 2006


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.Extension - Convenient definitions.

Open Issues

  • Should Prelude functions use Integer instead of Int?

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,

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]] wiki page.
class Functor f => Applicative f where
  -- lifting a value
  return :: a -> f a

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

  -- when the second is independent of the first
  -- included in the class in case performance can be enhanced
  (>>) :: m a -> m b -> m b

  -- intuitive definitions
  fa >> fb = (map (const id) fa) <*> fb    -- is there a better definition?
  x >>= f = join (map f x)
  join x = x >>= id

-- we shamelessly copy from the ''MonadPlus reform proposal'' now.

-- should satisfy 'left zero': zero >>= f = zero
-- zero will be used when pattern matching against refutable patterns in
-- do-notation as well as to provide support for monad comprehensions.
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

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