[commit: base] master: Add the IsList class, for OverloadedLists (ea5ccf1)

Simon Peyton Jones simonpj at microsoft.com
Fri Feb 15 18:22:17 CET 2013


Repository : ssh://darcs.haskell.org//srv/darcs/packages/base

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/ea5ccf1764812c6364da1879307d19de2d99eba4

>---------------------------------------------------------------

commit ea5ccf1764812c6364da1879307d19de2d99eba4
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date:   Fri Feb 15 17:21:54 2013 +0000

    Add the IsList class, for OverloadedLists

>---------------------------------------------------------------

 GHC/Exts.hs |   41 +++++++++++++++++++++++++++++++++++++++--
 1 files changed, 39 insertions(+), 2 deletions(-)

diff --git a/GHC/Exts.hs b/GHC/Exts.hs
index 79290fc..8191720 100755
--- a/GHC/Exts.hs
+++ b/GHC/Exts.hs
@@ -1,5 +1,5 @@
 {-# LANGUAGE Unsafe #-}
-{-# LANGUAGE MagicHash, UnboxedTuples, DeriveDataTypeable #-}
+{-# LANGUAGE MagicHash, UnboxedTuples, DeriveDataTypeable, TypeFamilies, MultiParamTypeClasses, FlexibleInstances #-}
 
 -----------------------------------------------------------------------------
 -- |
@@ -57,7 +57,10 @@ module GHC.Exts
         currentCallStack,
 
         -- * The Constraint kind
-        Constraint
+        Constraint,
+        
+        -- * Overloaded lists
+        IsList(..)
        ) where
 
 import Prelude
@@ -129,3 +132,37 @@ traceEvent = Debug.Trace.traceEventIO
 data SpecConstrAnnotation = NoSpecConstr | ForceSpecConstr
                 deriving( Data, Typeable, Eq )
 
+
+{- **********************************************************************
+*									*
+*              The IsList class                                         *
+*									*
+********************************************************************** -}
+
+-- | The 'IsList' class and its methods are intended to be used in
+--   conjunction with the OverloadedLists extension.
+class IsList l where
+  -- | The 'Item' type function returns the type of items of the structure
+  --   @l at .
+  type Item l
+  
+  -- | The 'fromList' function constructs the structure @l@ from the given
+  --   list of @Item l@
+  fromList  :: [Item l] -> l
+  
+  -- | The 'fromListN' function takes the input list's length as a hint. Its
+  --   behaviour should be equivalent to 'fromList'. The hint can be used to
+  --   construct the structure @l@ more efficiently compared to 'fromList'. If
+  --   the given hint does not equal to the input list's length the behaviour of
+  --   'fromListN' is not specified.
+  fromListN :: Int -> [Item l] -> l
+  fromListN _ = fromList
+  
+  -- | The 'toList' function extracts a list of @Item l@ from the structure @l at .
+  --   It should satisfy fromList . toList = id. 
+  toList :: l -> [Item l]
+
+instance IsList [a] where
+  type (Item [a]) = a
+  fromList = id
+  toList = id





More information about the ghc-commits mailing list