Difference between revisions of "The Other Prelude"

From HaskellWiki
Jump to navigation Jump to search
(Imported Prelude(id, const), now it compiles.)
(comment fmt, added Class Heirarchy Proposal (commented-out since invalid))
Line 22: Line 22:
 
== 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?
 
* 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>? 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?
 
* 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?
Line 30: 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. The [[class system extension proposal]] might make a difference.
   
 
== The Code ==
 
== The Code ==
Line 36: Line 35:
 
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 imaginary Prelude as it stands,
+
The imaginary Prelude as it stands:
   
 
=== <hask>TheOtherPrelude.hs</hask> ===
 
=== <hask>TheOtherPrelude.hs</hask> ===
Line 43: Line 42:
 
module TheOtherPrelude where
 
module TheOtherPrelude where
   
import Prelude (id, const) -- hide everything
+
import Prelude (id, const, flip) -- hide almost 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.
  +
-- 'map' is aliased as (.) below.
   
-- 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
 
class Functor f where
 
map :: (a -> b) -> f a -> f b
 
map :: (a -> b) -> f a -> f b
   
 
(.) :: (Functor f) => (a -> b) -> f a -> f b
 
(.) :: (Functor f) => (a -> b) -> f a -> f b
  +
(.) = map
(.) = 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
 
class (Functor p) => Applicative p where
 
-- Minimal complete definition: return and (<*>).
 
-- Minimal complete definition: return and (<*>).
Line 63: Line 62:
 
(>>) :: p a -> p b -> p b -- when the second is independent of the first
 
(>>) :: p a -> p b -> p b -- when the second is independent of the first
   
 
pa >> pb = map (const id) pa <*> pb
-- Default definition:
 
  +
--map f pa = return f <*> pa -- see Class system extension proposal, below
f >> g = (map (const id) f) <*> g
 
   
 
apply :: (Applicative p) => p (a -> b) -> p a -> p b
 
apply :: (Applicative p) => p (a -> b) -> p a -> p b
  +
apply = (<*>)
apply = (<*>) -- defined outside the class as a prefix synonym for (<*>).
 
   
 
class (Applicative m) => Monad m where
 
class (Applicative m) => Monad m where
Line 74: Line 73:
 
join :: m (m a) -> m a -- combining levels of structure
 
join :: m (m a) -> m a -- combining levels of structure
   
  +
ma >>= k = join (map k ma)
-- Default definitions:
 
x >>= f = join (map f x)
+
join mma = mma >>= id
  +
--mf <*> ma = mf >>= flip map ma -- see Class system extension proposal, below
join x = x >>= id
 
  +
--ma >> mb = ma >>= const mb
  +
--map f ma = ma >>= return . f -- this depends on (.), which is map! Be careful.
   
-- We shamelessly copy from the MonadPlus reform proposal (link below) now.
+
-- We copy from the MonadPlus reform proposal (link below) now.
 
-- '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.
  +
-- Should satisfy 'left zero': zero >>= f = zero
 
 
class (Monad mz) => MonadZero mz where
 
class (Monad mz) => MonadZero mz where
 
-- Should satisfy 'left zero': zero >>= f = zero
 
zero :: mz a
 
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
 
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
 
(++) :: 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
 
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
 
orElse :: mo a -> mo a -> mo a
 
</haskell>
 
</haskell>

Revision as of 17:00, 3 February 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

  • 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

module TheOtherPrelude where

import Prelude (id, const, flip) -- hide almost 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.
-- 'map' is aliased as (.) below.

class Functor f where
  map :: (a -> b) -> f a -> f b

(.) :: (Functor f) => (a -> b) -> f a -> f b
(.) = map

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

  pa >> pb = map (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

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