Type without a data constructor?

Most examples for defining algebraic types include data constructors like so: data Tree a = Tip | Node a (Tree a) (Tree a) I by mistake defined a type which did not specify a data constructor : data SearchCondition = Term Bool | SearchCondition :||: (Term Bool) data Term a = Constant a sc :: SearchCondition sc = Term True is ok, but sc :: SearchCondition sc = Constant True is not (though this is what I intended to capture!). So the question is what are types with no constructors good for? A simple example would be appreciated. Rahul

On Monday 06 August 2007 19:23, Rahul Kapoor wrote:
Most examples for defining algebraic types include data constructors like so:
data Tree a = Tip | Node a (Tree a) (Tree a)
I by mistake defined a type which did not specify a data constructor :
In this example, you have two different uses of the lexical name 'Term', and I think it is confusing you. One kind of use is as a data constructor; the other is as a type constructor. I've annotated the uses below:
data SearchCondition = Term Bool -- data constructor | SearchCondition :||: (Term Bool) -- type constructor
data Term a = Constant a -- defn of type constr 'Term'
sc :: SearchCondition sc = Term True -- data constructor
is ok, but
sc :: SearchCondition sc = Constant True
Now, here you have an expression of type 'Term Bool'. These can only appear on the right-hand side of :||: . This probably isn't what you want. Likely what you actually want is:
data SearchCondition = SearchTerm (Term Bool) | SearchCondition :||: (Term Bool)
Here, both uses of 'Term' refer to the type constructor.
is not (though this is what I intended to capture!).
So the question is what are types with no constructors good for? A simple example would be appreciated.
There are some situations where an explicitly empty type is useful. Type-level programming voodoo is one. Other times the void type is nice because it can be used as a parameter to a type constructor. For example, if you use the nested datatype representation of de Bruijn lambda terms [1], you can use the void type to create the type of closed terms (terms with no free variables). Here's the short version: data Void data Succ a = Zero | Incr a data Term a = Var a | App (Term a) (Term a) | Lam (Term (Succ a)) type ClosedTerm = Term Void [1] Richard Bird and Ross Patterson, _de Brujin Notation as a Nested Datatype_, Journal of Functional Programming 9(1):77-91, January 1999. Rob Dockins

Hi
I by mistake defined a type which did not specify a data constructor
So the question is what are types with no constructors good for? A simple example would be appreciated.
They are called phantom types, and can be used for ensuring properties at the type level. I wrote about them in a blog post: http://neilmitchell.blogspot.com/2007/04/phantom-types-for-real-problems.htm... There are probably better references, but that's the easiest for me to find ;-) Thanks Neil

The answer would be phantom types, but your example doesn't use them. Each of your types has at least one constructor: Possibly you overlooked the infix constructor :||: ? Tree a has 2 constructors: Tip and Node SearchCondition has 2 constructors: Term and (:||:) Term a has 1 constructor : Constant *Prelude> :t Tip Tip :: Tree a *Prelude> :t Node Node :: a -> Tree a -> Tree a -> Tree a *Prelude> :t Term True Term True :: SearchCondition *Prelude> :t (:||:) (:||:) :: SearchCondition -> Term Bool -> SearchCondition *Prelude> :t Constant True Constant True :: Term Bool Dan Weston Rahul Kapoor wrote:
Most examples for defining algebraic types include data constructors like so:
data Tree a = Tip | Node a (Tree a) (Tree a)
I by mistake defined a type which did not specify a data constructor :
data SearchCondition = Term Bool | SearchCondition :||: (Term Bool) data Term a = Constant a
sc :: SearchCondition sc = Term True
is ok, but
sc :: SearchCondition sc = Constant True
is not (though this is what I intended to capture!).
So the question is what are types with no constructors good for? A simple example would be appreciated.
Rahul _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On 2007-08-06, Rahul Kapoor
I by mistake defined a type which did not specify a data constructor :
No, you didn't. Both types have data constructors.
data SearchCondition = Term Bool | SearchCondition :||: (Term Bool) data Term a = Constant a
sc :: SearchCondition sc = Term True
is ok, but
sc :: SearchCondition sc = Constant True
is not (though this is what I intended to capture!).
The problem is that Constant True is of type Term Bool, rather than SearchCondition. Constructors and names of data types live in separate namespaces.
So the question is what are types with no constructors good for? A simple example would be appreciated.
See the phantom types answer that someone else gave. -- Aaron Denney -><-
participants (5)
-
Aaron Denney
-
Dan Weston
-
Neil Mitchell
-
Rahul Kapoor
-
Robert Dockins