#7495: Rebindable list syntax?
-----------------------------+----------------------------------------------
Reporter:  nwf               |          Owner:                  
    Type:  feature request   |         Status:  new             
Priority:  normal            |      Component:  Compiler        
 Version:  7.6.1             |       Keywords:                  
      Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple
 Failure:  None/Unknown      |      Blockedby:                  
Blocking:                    |        Related:                  
-----------------------------+----------------------------------------------
 First, sorry if I've missed an earlier request for this in trac; a few
 searches did not turn up anything relevant.

 I've recently taken to doing a lot of work with heterogenous lists (thanks
 to the DataKinds work) and find the forced-cons-and-nil style of writing
 lists (e.g. "a:+b:+c:+HN") to be sort of unpleasant.

 Would it be possible to allow rebinding list-literal syntax?  Off the top
 of my head I think something like the following might be workable, if only
 I could stop [] and (:) from being in scope, even with
 -XNoImplicitPrelude.  (Example requires -XDataKinds -XFlexibleInstances
 -XGADTs -XMultiParamTypeClasses -XTypeOperators)

 {{{
 class HasNil a where
   ([])  :: a
   isNil :: a -> Bool

 class HasCons e l l' | e l -> l', l' -> e l where
   (:)    :: e -> l -> l'
   uncons :: l' -> Maybe (e,l)

 -- For homogeneous lists...
 instance HasNil [a] where
   ([])  = ([])
   isNil = null

 instance (a ~ a1, a ~ a2) => HasCons a [a1] [a2] where
   (:)           = (:)
   uncons []     = Nothing
   uncons (x:xs) = Just (x,xs)

 -- For HLists...
 data HList as where
   HN   :: HList '[]
   (:+) :: a -> HList as -> HList (a ': as)

 instance HasNil (HList '[]) where
   ([])  = HN
   isNil = const True

 instance (a ~ a1, as ~ as1) => HasCons a (HList as) (HList (a1 ': as1))
 where
   (:)              = (:+)
   uncons (a :+ as) = Just (a,as)
 }}}

-- 
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/7495>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler

_______________________________________________
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to