Ignore some orphan warnings
[ghc-base.git] / Data / Generics / Aliases.hs
index e28a623..024c3de 100644 (file)
@@ -6,7 +6,7 @@
 -- 
 -- Maintainer  :  libraries@haskell.org
 -- Stability   :  experimental
--- Portability :  non-portable
+-- Portability :  non-portable (local universal quantification)
 --
 -- \"Scrap your boilerplate\" --- Generic programming in Haskell 
 -- See <http://www.cs.vu.nl/boilerplate/>. The present module provides
 --
 -----------------------------------------------------------------------------
 
-module Data.Generics.Aliases ( 
+module Data.Generics.Aliases (
 
-       -- * Combinators to \"make\" generic functions via cast
-       mkT, mkQ, mkM, mkMp, mkR,
-       extT, extQ, extM, extMp, extB, extR,
+        -- * Combinators to \"make\" generic functions via cast
+        mkT, mkQ, mkM, mkMp, mkR,
+        ext0, extT, extQ, extM, extMp, extB, extR,
 
-       -- * Type synonyms for generic function types
-       GenericT, 
-       GenericQ,
-       GenericM,
-       GenericB,
-       GenericR,
+        -- * Type synonyms for generic function types
+        GenericT,
+        GenericQ,
+        GenericM,
+        GenericB,
+        GenericR,
         Generic,
         Generic'(..),
         GenericT'(..),
         GenericQ'(..),
         GenericM'(..),
 
-       -- * Inredients of generic functions
-       orElse,
+        -- * Inredients of generic functions
+        orElse,
 
-       -- * Function combinators on generic functions
-       recoverMp,
-       recoverQ,
-       choiceMp,
-       choiceQ,
+        -- * Function combinators on generic functions
+        recoverMp,
+        recoverQ,
+        choiceMp,
+        choiceQ,
 
-        -- * Operators for (over-appreciated) unfolding
-        gunfoldB,
-        gunfoldR,
-
-       -- * Type extension for lists
-       extListT, 
-       extListM,
-       extListQ,
-       extListR
+        -- * Type extension for unary type constructors
+        ext1T,
+        ext1M,
+        ext1Q,
+        ext1R
 
   ) where
 
@@ -62,8 +58,8 @@ import Data.Generics.Basics
 
 ------------------------------------------------------------------------------
 --
---     Combinators to "make" generic functions
---     We use type-safe cast in a number of ways to make generic functions.
+--      Combinators to "make" generic functions
+--      We use type-safe cast in a number of ways to make generic functions.
 --
 ------------------------------------------------------------------------------
 
@@ -75,11 +71,9 @@ mkT :: ( Typeable a
        , Typeable b
        )
     => (b -> b)
-    -> a 
     -> a
-mkT f = case cast f of
-               Just g -> g
-               Nothing -> id
+    -> a
+mkT = extT id
 
 
 -- | Make a generic query;
@@ -91,7 +85,7 @@ mkQ :: ( Typeable a
        )
     => r
     -> (b -> r)
-    -> a 
+    -> a
     -> r
 (r `mkQ` br) a = case cast a of
                         Just b  -> br b
@@ -107,7 +101,7 @@ mkM :: ( Monad m
        , Typeable b
        )
     => (b -> m b)
-    -> a 
+    -> a
     -> m a
 mkM = extM return
 
@@ -148,18 +142,18 @@ mkR f = mzero `extR` f
 
 -- | Flexible type extension
 ext0 :: (Typeable a, Typeable b) => c a -> c b -> c a
-ext0 def ext = maybe def id (cast0 ext)
+ext0 def ext = maybe def id (gcast ext)
 
 
 -- | Extend a generic transformation by a type-specific case
 extT :: ( Typeable a
-        , Typeable b 
+        , Typeable b
         )
      => (a -> a)
      -> (b -> b)
      -> a
      -> a
-extT f = maybe f id . cast
+extT def ext = unT ((T def) `ext0` (T ext))
 
 
 -- | Extend a generic query by a type-specific case
@@ -211,7 +205,7 @@ extR def ext = unR ((R def) `ext0` (R ext))
 
 ------------------------------------------------------------------------------
 --
---     Type synonyms for generic function types
+--      Type synonyms for generic function types
 --
 ------------------------------------------------------------------------------
 
@@ -260,9 +254,9 @@ data Generic' c = Generic' { unGeneric' :: Generic c }
 
 
 -- | Other first-class polymorphic wrappers
-newtype GenericT'   = GenericT' { unGenericT' :: Data a => a -> a }
-newtype GenericQ' r = GenericQ' { unGenericQ' :: GenericQ r }
-newtype GenericM' m = GenericM' { unGenericM' :: Data a => a -> m a }
+newtype GenericT'   = GT { unGT :: Data a => a -> a }
+newtype GenericQ' r = GQ { unGQ :: GenericQ r }
+newtype GenericM' m = GM { unGM :: Data a => a -> m a }
 
 
 -- | Left-biased choice on maybies
@@ -307,71 +301,56 @@ recoverQ r f = f `choiceQ` const (return r)
 
 ------------------------------------------------------------------------------
 --
---     Generic unfolding
+--      Type extension for unary type constructors
 --
 ------------------------------------------------------------------------------
 
--- | Construct an initial term with undefined immediate subterms
---   and then map over the skeleton to fill in proper terms.
-gunfoldB :: Data a
-         => Constr
-         -> (forall a. Data a => a)
-         -> a
-gunfoldB c f = gmapT (const f) (fromConstr c)
-
-
--- | Monadic variation on \"gunfoldB\"
-gunfoldR :: (Monad m, Data a)
-         => Constr
-         -> (forall a. Data a => m a)
-         -> m a
-gunfoldR c f = gmapM (const f) $ fromConstr c
 
 
-
-------------------------------------------------------------------------------
---
---     Type extension for lists
---
-------------------------------------------------------------------------------
+-- | Flexible type extension
+ext1 :: (Data a, Typeable1 t)
+     => c a
+     -> (forall a. Data a => c (t a))
+     -> c a
+ext1 def ext = maybe def id (dataCast1 ext)
 
 
--- | Type extension of transformations for lists
-extListT :: Data d
-         => (forall d. Data d => d -> d)
-         -> (forall d. Data d => [d] -> [d])
-         -> d -> d
-extListT def ext = unT ((T def) `ext1` (T ext))
+-- | Type extension of transformations for unary type constructors
+ext1T :: (Data d, Typeable1 t)
+      => (forall d. Data d => d -> d)
+      -> (forall d. Data d => t d -> t d)
+      -> d -> d
+ext1T def ext = unT ((T def) `ext1` (T ext))
 
 
--- | Type extension of monadic transformations for lists
-extListM :: (Monad m, Data d)
-         => (forall d. Data d => d -> m d)
-         -> (forall d. Data d => [d] -> m [d])
-         -> d -> m d
-extListM def ext = unM ((M def) `ext1` (M ext))
+-- | Type extension of monadic transformations for type constructors
+ext1M :: (Monad m, Data d, Typeable1 t)
+      => (forall d. Data d => d -> m d)
+      -> (forall d. Data d => t d -> m (t d))
+      -> d -> m d
+ext1M def ext = unM ((M def) `ext1` (M ext))
 
 
--- | Type extension of queries for lists
-extListQ :: Data d
-         => (d -> q)
-         -> (forall d. Data d => [d] -> q)
-         -> d -> q
-extListQ def ext = unQ ((Q def) `ext1` (Q ext))
+-- | Type extension of queries for type constructors
+ext1Q :: (Data d, Typeable1 t)
+      => (d -> q)
+      -> (forall d. Data d => t d -> q)
+      -> d -> q
+ext1Q def ext = unQ ((Q def) `ext1` (Q ext))
 
 
--- | Type extension of readers for lists
-extListR :: (Monad m, Data d)
-         => m d
-         -> (forall d. Data d => m [d])
-         -> m d
-extListR def ext = unR ((R def) `ext1` (R ext))
+-- | Type extension of readers for type constructors
+ext1R :: (Monad m, Data d, Typeable1 t)
+      => m d
+      -> (forall d. Data d => m (t d))
+      -> m d
+ext1R def ext = unR ((R def) `ext1` (R ext))
 
 
 
 ------------------------------------------------------------------------------
 --
---     Type constructors for type-level lambdas
+--      Type constructors for type-level lambdas
 --
 ------------------------------------------------------------------------------