Proposal: Add a Void1 :: * -> * type to base

Hi, Recently I found myself in need of a type like Void, but taking a type parameter, so I wrote up a fairly simple implementation inspired by Data.Void: {-# LANGUAGE DeriveDataTypeable #-} {-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE EmptyCase #-} {-# LANGUAGE StandaloneDeriving #-} data Void1 a deriving Generic deriving instance Data a => Data (Void1 a) instance Ix (Void1 a) where range _ = [] index _ = absurd1 inRange _ = absurd1 rangeSize _ = 0 instance Typeable a => Exception (Void1 a) instance Eq (Void1 a) where _ == _ = True instance Ord (Void1 a) where compare _ _ = EQ instance Read (Void1 a) where readsPrec _ _ = [] instance Semigroup (Void1 a) where a <> _ = a instance Show (Void1 a) where show = absurd1 instance Functor Void1 where fmap _ = absurd1 instance Foldable Void1 where foldMap _ = absurd1 instance Traversable Void1 where traverse _ = absurd1 absurd1 :: Void1 a -> b absurd1 v = case v of {} (If we step outside the realm of base, this type is also a Contravariant and a Comonad) I left this sitting alone in a Utils module until last night when I saw someone ask in #haskell if there was "a Void1 type defined in some central place". So, in case this is of more general interest, I propose that a module Data.Functor.Void be added to base. Another colour to paint this bikeshed would be "VoidF", rather than "Void1". Also, this could be added to Data.Void rather than be a new module, but I think it's more sensible to include in the Data.Functor hierarchy, perhaps with a re-export from Data.Void. Discussion period: 2 weeks (ending Wed, 1st March) -- Michael Walker (http://www.barrucadu.co.uk)

On Wed, Feb 15, 2017 at 3:31 PM, Michael Walker
I left this sitting alone in a Utils module until last night when I saw someone ask in #haskell if there was "a Void1 type defined in some central place". So, in case this is of more general interest, I propose that a module Data.Functor.Void be added to base.
I think the bar for adding things to base is higher than "two people found it useful"...

I think there was some discussion of this recently. We already have V1 in
GHC.Generics; perhaps that could be given a better name.
On Feb 15, 2017 6:55 PM, "Bryan O'Sullivan"
On Wed, Feb 15, 2017 at 3:31 PM, Michael Walker
wrote: I left this sitting alone in a Utils module until last night when I saw someone ask in #haskell if there was "a Void1 type defined in some central place". So, in case this is of more general interest, I propose that a module Data.Functor.Void be added to base.
I think the bar for adding things to base is higher than "two people found it useful"...
_______________________________________________ Libraries mailing list Libraries@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/libraries
participants (3)
-
Bryan O'Sullivan
-
David Feuer
-
Michael Walker