Need an example of new type constructor with zero data constructors

In the Haskell report 2010, a data declaration has the format of: https://lh3.googleusercontent.com/-G-z92n-50B0/V63XKCCrJDI/AAAAAAAAAGA/w-Zdi... For a new type, there could be zero or more data constructors. What's the use case for a new type that has zero data constructor?

I haven't used Void enough to really be able to answer this, so here are
some links to information about the empty type.
https://wiki.haskell.org/Empty_type
https://hackage.haskell.org/package/void
http://stackoverflow.com/questions/14131856/whats-the-absurd-function-in-dat...
Hope that helps.
James Brown
In the Haskell report 2010, a data declaration has the format of:
https://lh3.googleusercontent.com/-G-z92n-50B0/V63XKCCrJDI/AAAAAAAAAGA/w-Zdi...
For a new type, there could be zero or more data constructors. What's the use case for a new type that has zero data constructor? _______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.
-- Jack

What you posted is the format for data declarations, not newtypes. Newtypes
are required to have exactly one constructor:
newtype [context =>] simpletype = newconstr [deriving]
Adam
On Fri, Aug 12, 2016 at 4:43 PM, James Brown
In the Haskell report 2010, a data declaration has the format of:
https://lh3.googleusercontent.com/-G-z92n-50B0/V63XKCCrJDI/AAAAAAAAAGA/w-Zdi...
For a new type, there could be zero or more data constructors. What's the use case for a new type that has zero data constructor?
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.

I think they mean "new type" to mean a data declaration, rather than a
newtype. I had to read it a few times before it clicked for me. Just a
confusion in terminology.
Adam Bergmark
What you posted is the format for data declarations, not newtypes. Newtypes are required to have exactly one constructor:
newtype [context =>] simpletype = newconstr [deriving]
Adam
On Fri, Aug 12, 2016 at 4:43 PM, James Brown
wrote: In the Haskell report 2010, a data declaration has the format of:
https://lh3.googleusercontent.com/-G-z92n-50B0/V63XKCCrJDI/AAAAAAAAAGA/w-Zdi...
For a new type, there could be zero or more data constructors. What's the use case for a new type that has zero data constructor?
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.
-- Jack

For zero data constructors you need to use only EmptyDataDecls https://prime.haskell.org/wiki/EmptyDataDecls extension.

What's the purpose to allow data declarations with no constructors?
On Fri, Aug 12, 2016 at 11:08 AM, Sergey N. Yashin
For zero data constructors you need to use only EmptyDataDecls https://prime.haskell.org/wiki/EmptyDataDecls extension.
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.

For example empty data declarations, *Fst *and *Snd *in the code bellow: {-# LANGUAGE TypeOperators #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE EmptyDataDecls #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE FlexibleInstances #-} module Main where data Fst data Snd data F a b = F b deriving Show data S a b = S b deriving Show class TupleVal a where val :: a b -> b instance a ~ Fst => TupleVal (F a) where val (F v) = v instance a ~ Fst => TupleVal (S a) where val (S v) = v class TupleOps (a :: * -> * -> *) b c where type FST a b c type SND a b c tfst :: a b c -> FST a b c tsnd :: a b c -> SND a b c instance (b ~ F b' b'', b' ~ Fst, c ~ S c' c'', c' ~ Snd) => TupleOps (,) b c where type FST (,) b c = b type SND (,) b c = c tfst = fst tsnd = snd instance TupleOps F b (c1, c2) where type FST F b (c1, c2) = c1 type SND F b (c1, c2) = c2 tfst (F (v1, v2)) = v1 tsnd (F (v1, v2)) = v2 instance TupleOps S b (c1, c2) where type FST S b (c1, c2) = c1 type SND S b (c1, c2) = c2 tfst (S (v1, v2)) = v1 tsnd (S (v1, v2)) = v2 type First a = F Fst a type Second a = S Snd a type a @@ b = (First a, Second b) type family a :=: b where Fst :=: b = Fst' b Snd :=: b = Snd' b infixr 1 :=: type family Fst' a where Fst' (a, b) = a Fst' (First a) = Fst' a Fst' (Second a) = Fst' a type family Snd' a where Snd' (a, b) = b Snd' (First a) = Snd' a Snd' (Second a) = Snd' a (@@) :: a -> b -> a @@ b a @@ b = (F a, S b) tpl1 :: Int @@ String tpl1 = 1 @@ "hello" tpl2 :: Snd :=: String @@ String tpl2 = tsnd ("hello" @@ "world") tpl3 :: Snd :=: String @@ String tpl3 = tsnd ("hello" @@ "world") tpl4 :: Int @@ String tpl4 = 1 @@ "hello" tpl5 :: Snd :=: String @@ (String @@ String) tpl5 = tsnd ("hello" @@ ("hello" @@ "world")) tpl6 :: Snd :=: Fst :=: Snd :=: (String @@ String) @@ ((String @@ String) @@ String) tpl6 = tsnd . tfst . tsnd $ ("world1" @@ "hello2") @@ (("hello3" @@ "world5") @@ "world4") main :: IO () main = do print tpl4 print tpl3 print tpl2 print tpl6 пятница, 12 августа 2016 г., 18:16:18 UTC+3 пользователь James Brown написал:
What's the purpose to allow data declarations with no constructors?
On Fri, Aug 12, 2016 at 11:08 AM, Sergey N. Yashin
javascript:> wrote: For zero data constructors you need to use only EmptyDataDecls https://prime.haskell.org/wiki/EmptyDataDecls extension.
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.

One use is when you want an open sum type rather than a closed one. For
example, you might want users of your library to add their own
'constructors'. Then, they serve a purpose similar to a constructor that
takes no arguments:
{-# LANGUAGE EmptyDataDecls #-}
class Color a where
rgb :: a -> (Int, Int, Int)
data Red
data Green
data Blue
instance Color Red where
rgb _ = (255, 0, 0)
instance Color Green where
rgb _ = (0, 255, 0)
instance Color Blue where
rgb _ = (0, 0, 255)
data ColorADT = Color_Red | Color_Green | Color_Blue
rgb_adt Color_Red = (255, 0, 0)
rgb_adt Color_Green = (0, 255, 0)
rgb_adt Color_Blue = (0, 0, 255)
On Fri, Aug 12, 2016 at 8:16 AM, James Brown
What's the purpose to allow data declarations with no constructors?
On Fri, Aug 12, 2016 at 11:08 AM, Sergey N. Yashin < yashin.sergey@gmail.com> wrote:
For zero data constructors you need to use only EmptyDataDecls https://prime.haskell.org/wiki/EmptyDataDecls extension.
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.

Another use: class Foo a e | a -> e where foo :: a -> Either e a instance Foo Int Void where foo :: Int -> Either Void Int foo x = Right (x + 1) Even though it's an "Either", we're saying we will never (ignoring bottom) return a "Left" value. Tom
El 12 ago 2016, a las 11:28, Michael Burge
escribió: One use is when you want an open sum type rather than a closed one. For example, you might want users of your library to add their own 'constructors'. Then, they serve a purpose similar to a constructor that takes no arguments:
{-# LANGUAGE EmptyDataDecls #-}
class Color a where rgb :: a -> (Int, Int, Int)
data Red data Green data Blue
instance Color Red where rgb _ = (255, 0, 0)
instance Color Green where rgb _ = (0, 255, 0)
instance Color Blue where rgb _ = (0, 0, 255)
data ColorADT = Color_Red | Color_Green | Color_Blue rgb_adt Color_Red = (255, 0, 0) rgb_adt Color_Green = (0, 255, 0) rgb_adt Color_Blue = (0, 0, 255)
On Fri, Aug 12, 2016 at 8:16 AM, James Brown
wrote: What's the purpose to allow data declarations with no constructors? On Fri, Aug 12, 2016 at 11:08 AM, Sergey N. Yashin
wrote: For zero data constructors you need to use only EmptyDataDecls extension. _______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.
participants (6)
-
Adam Bergmark
-
amindfv@gmail.com
-
Jack Henahan
-
James Brown
-
Michael Burge
-
Sergey N. Yashin