Data type definition for a list of elements of alternating types?

-- As an exercise I wanted to define a datatype that is an alternating list of elements of two different types. The best that I could do are the type definitions below: module BiList ( BiList (..) , AList (EmptyA) , BList (EmptyB) ) where data BiList a b = Empty | BA (AList a b) | BB (BList a b) data AList a b = EmptyA | AL a (BList a b) data BList a b = EmptyB | BL b (AList a b) (<#) :: a -> (BList a b) -> (AList a b) a <# bs = AL a bs (<@) :: b -> (AList a b) -> (BList a b) b <@ as = BL b as infixr 5 <# infixr 5 <@ example :: BiList Int Char example = BA $ 1 <# 'a' <@ 2 <# 'b' <@ 3 <# 'c' <@ 4 <# 'd' <@ EmptyA -- There are two things that I don't like about this implementation. -- (1) The BA and BB constructors that must be applied on top of instances of (AList a b) and (BList a b) to lift them to be of type (BiList a b). -- (2) Having three different constructors for an empty list: Empty, EmptyA, EmptyB, where ideally I would just have one. -- Is it possible to get around either of these annoyances with some type theory gymnastics? Maybe something like the function fromIntegral (the mechanics of which I don't really understand at this point)?

Would this work for you?
data BiList a b
= Empty
| a :# (BiList b a)
infixr 5 :#
blah :: BiList Char Int
blah = 'a' :# 1 :# 'a' :# Empty
On Wed, Apr 2, 2014 at 9:52 PM, Jacek Dudek
-- As an exercise I wanted to define a datatype that is an alternating list of elements of two different types. The best that I could do are the type definitions below:
module BiList ( BiList (..) , AList (EmptyA) , BList (EmptyB) ) where
data BiList a b = Empty | BA (AList a b) | BB (BList a b)
data AList a b = EmptyA | AL a (BList a b)
data BList a b = EmptyB | BL b (AList a b)
(<#) :: a -> (BList a b) -> (AList a b) a <# bs = AL a bs
(<@) :: b -> (AList a b) -> (BList a b) b <@ as = BL b as
infixr 5 <# infixr 5 <@
example :: BiList Int Char example = BA $ 1 <# 'a' <@ 2 <# 'b' <@ 3 <# 'c' <@ 4 <# 'd' <@ EmptyA
-- There are two things that I don't like about this implementation.
-- (1) The BA and BB constructors that must be applied on top of instances of (AList a b) and (BList a b) to lift them to be of type (BiList a b).
-- (2) Having three different constructors for an empty list: Empty, EmptyA, EmptyB, where ideally I would just have one.
-- Is it possible to get around either of these annoyances with some type theory gymnastics? Maybe something like the function fromIntegral (the mechanics of which I don't really understand at this point)? _______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

On Wed, Apr 02, 2014 at 09:52:21PM -0400, Jacek Dudek wrote:
-- As an exercise I wanted to define a datatype that is an alternating list of elements of two different types. The best that I could do are the type definitions below:
module BiList ( BiList (..) , AList (EmptyA) , BList (EmptyB) ) where
data BiList a b = Empty | BA (AList a b) | BB (BList a b)
data AList a b = EmptyA | AL a (BList a b)
data BList a b = EmptyB | BL b (AList a b)
(<#) :: a -> (BList a b) -> (AList a b) a <# bs = AL a bs
(<@) :: b -> (AList a b) -> (BList a b) b <@ as = BL b as
infixr 5 <# infixr 5 <@
example :: BiList Int Char example = BA $ 1 <# 'a' <@ 2 <# 'b' <@ 3 <# 'c' <@ 4 <# 'd' <@ EmptyA
As David McBride noted, AList and BList are isomorphic (up to the order of their arguments) so you don't need both. Unfortunately you do still need BiList; but you don't need its Empty. So: data BiList a b = BA (AltList a b) | BB (AltList b a) data AltList a b = Empty | Cons a (AltList b a) So this addresses (2) but not (1). I don't think there is any way around the need for (1). (Note, however, that you do still have two distinct representations of the empty list: BA Empty and BB Empty. I can't see any way around that either.) -Brent

On 3 April 2014 22:58, Brent Yorgey
data BiList a b = BA (AltList a b) | BB (AltList b a)
data AltList a b = Empty | Cons a (AltList b a)
So this addresses (2) but not (1). I don't think there is any way around the need for (1). (Note, however, that you do still have two distinct representations of the empty list: BA Empty and BB Empty. I can't see any way around that either.)
You could move the Empty constructor to BiList while making AltList a non-empty list, i.e. data BiList a b = Empty | BA (AltList a b) | BB (AltList b a) data AltList a b = Elem a | Cons a (AltList b a) -- Denis Kasak

Thanks David, that's really clever! I was trying to do it without any
auxiliary data types, but couldn't see how I could use an instance of
(BiList a b) in the constructor expression for (BiList a b) without
losing the property that the list elements alternate from one type to
the other with each new element.
But now I see that when you write (BiList b a) in the constructor
expression, that's written in the context provided by the (data BiList
a b) line, so having the type variables in the opposite order makes
all the difference.
Brent, David's definition actually solved both (1) and (2), try it out!
On 4/3/14, Denis Kasak
On 3 April 2014 22:58, Brent Yorgey
wrote: data BiList a b = BA (AltList a b) | BB (AltList b a)
data AltList a b = Empty | Cons a (AltList b a)
So this addresses (2) but not (1). I don't think there is any way around the need for (1). (Note, however, that you do still have two distinct representations of the empty list: BA Empty and BB Empty. I can't see any way around that either.)
You could move the Empty constructor to BiList while making AltList a non-empty list, i.e.
data BiList a b = Empty | BA (AltList a b) | BB (AltList b a)
data AltList a b = Elem a | Cons a (AltList b a)
-- Denis Kasak _______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

Ah, yes, having a nonempty AltList and moving Empty to BiList is a good idea. You still do need two different constructors BA and BB, but yes, overall this seems like a nice way to encode things. Exercise: write a conversion function fromList :: [Either a b] -> Maybe (BiList a b) which returns Just when the input list really is alternating, and Nothing otherwise. -Brent On Thu, Apr 03, 2014 at 10:04:04PM -0400, Jacek Dudek wrote:
Thanks David, that's really clever! I was trying to do it without any auxiliary data types, but couldn't see how I could use an instance of (BiList a b) in the constructor expression for (BiList a b) without losing the property that the list elements alternate from one type to the other with each new element.
But now I see that when you write (BiList b a) in the constructor expression, that's written in the context provided by the (data BiList a b) line, so having the type variables in the opposite order makes all the difference.
Brent, David's definition actually solved both (1) and (2), try it out!
On 4/3/14, Denis Kasak
wrote: On 3 April 2014 22:58, Brent Yorgey
wrote: data BiList a b = BA (AltList a b) | BB (AltList b a)
data AltList a b = Empty | Cons a (AltList b a)
So this addresses (2) but not (1). I don't think there is any way around the need for (1). (Note, however, that you do still have two distinct representations of the empty list: BA Empty and BB Empty. I can't see any way around that either.)
You could move the Empty constructor to BiList while making AltList a non-empty list, i.e.
data BiList a b = Empty | BA (AltList a b) | BB (AltList b a)
data AltList a b = Elem a | Cons a (AltList b a)
-- Denis Kasak _______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

See the separated package on hackage.
On 03/04/2014 2:53 PM, "Jacek Dudek"
-- As an exercise I wanted to define a datatype that is an alternating list of elements of two different types. The best that I could do are the type definitions below:
module BiList ( BiList (..) , AList (EmptyA) , BList (EmptyB) ) where
data BiList a b = Empty | BA (AList a b) | BB (BList a b)
data AList a b = EmptyA | AL a (BList a b)
data BList a b = EmptyB | BL b (AList a b)
(<#) :: a -> (BList a b) -> (AList a b) a <# bs = AL a bs
(<@) :: b -> (AList a b) -> (BList a b) b <@ as = BL b as
infixr 5 <# infixr 5 <@
example :: BiList Int Char example = BA $ 1 <# 'a' <@ 2 <# 'b' <@ 3 <# 'c' <@ 4 <# 'd' <@ EmptyA
-- There are two things that I don't like about this implementation.
-- (1) The BA and BB constructors that must be applied on top of instances of (AList a b) and (BList a b) to lift them to be of type (BiList a b).
-- (2) Having three different constructors for an empty list: Empty, EmptyA, EmptyB, where ideally I would just have one.
-- Is it possible to get around either of these annoyances with some type theory gymnastics? Maybe something like the function fromIntegral (the mechanics of which I don't really understand at this point)? _______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
participants (5)
-
Brent Yorgey
-
David McBride
-
Denis Kasak
-
Jacek Dudek
-
Tony Morris