RE: [Haskell-cafe] Newbie Question on type constructors

Most interesting discussion -- in reading it, I realized that I had a 'hidden agenda' in asking my question (hidden even from myself), and that is: can I put interesting functionality, like precondition checks & data validation, in data constructors? I suspect not, and that's why I tend to write something like the following: data Shape = Circle Float | Square Float deriving (Eq, Show) circle :: Float -> Shape circle x = if (x <= 0) then error "Bad radius!" else Circle x That's fine, but I don't know how to prevent users from calling "Circle" directly (in some other languages, I could declare the raw constructor to be "private", and, in Haskell, there may be some way for me to hack module exports to hide the raw constructor, but I haven't seen a way to do that). In any event, it might be useful if I could have some pattern to prevent circumvention of initialization code. Advice? -----Original Message----- From: haskell-cafe-bounces@haskell.org [mailto:haskell-cafe-bounces@haskell.org] On Behalf Of Ben Rudiak-Gould Sent: Monday, November 01, 2004 11:33 AM To: finnw@iname.com Cc: haskell-cafe@haskell.org Subject: Re: [Haskell-cafe] Newbie Question on type constructors Finn Wilcox wrote:
On Mon, 1 Nov 2004, Ben Rudiak-Gould wrote:
In particular, one cannot write an invert :: (a->b) -> Maybe (b->a) which never returns a wrong answer, except for invert = const Nothing > >How about:
invert = undefined
This never returns an answer at all, so it can't return a wrong one!
Sorry, I should have been clearer: my Nothing return was intended to mean "I don't know an answer", not "there is no answer". So my const Nothing is like your undefined, a function which never returns an answer (and thus never returns a wrong one). -- Ben _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On 2004-11-01 at 12:30PST "Brian Beckman" wrote:
Most interesting discussion -- in reading it, I realized that I had a 'hidden agenda' in asking my question (hidden even from myself), and that is: can I put interesting functionality, like precondition checks & data validation, in data constructors?
No, though one could make a case that you should be able to.
I suspect not, and that's why I tend to write something like the following:
data Shape = Circle Float | Square Float deriving (Eq, Show)
circle :: Float -> Shape circle x = if (x <= 0) then error "Bad radius!" else Circle x
That's fine,
Yup.
but I don't know how to prevent users from calling "Circle" directly
Put the data declaration in a module, export the type, but not the constructor you want to hide:
module Shape (Shape(Square), circle) where
-- Jón Fairbairn Jon.Fairbairn@cl.cam.ac.uk

On Monday 01 November 2004 21:51, Jon Fairbairn wrote:
On 2004-11-01 at 12:30PST "Brian Beckman" wrote:
Most interesting discussion -- in reading it, I realized that I had a 'hidden agenda' in asking my question (hidden even from myself), and that is: can I put interesting functionality, like precondition checks & data validation, in data constructors?
No, though one could make a case that you should be able to.
And there are (experimental) languages in which you can, see e.g. Cayenne or Epigram. 'Dependent Types' is the keyword here.
I suspect not, and that's why I tend to write something like the following:
data Shape = Circle Float
| Square Float
deriving (Eq, Show)
circle :: Float -> Shape circle x = if (x <= 0) then error "Bad radius!" else Circle x
That's fine,
Yup.
but I don't know how to prevent users from calling "Circle" directly
Put the data declaration in a module, export the type, but
not the constructor you want to hide:
module Shape (Shape(Square), circle) where
Since we were talking about 'what can one do with a constructor as compared with a function', it should be mentioned that this also has a disadvantage: you loose pattern matching outside the module. I.e. no longer can say ... case x of Circle radius -> ... Square edge -> ... BTW, would it be possible (in principle) to allow constructor export 'read-only', so matching against a constructor is allowed but not constructing a value? Ben

On 2004-11-01 at 23:01+0100 Benjamin Franksen wrote:
On Monday 01 November 2004 21:51, Jon Fairbairn wrote:
Put the data declaration in a module, export the type, but
not the constructor you want to hide:
module Shape (Shape(Square), circle) where
Since we were talking about 'what can one do with a constructor as compared with a function', it should be mentioned that this also has a disadvantage: you loose pattern matching outside the module. I.e. no longer can say
... case x of Circle radius -> ... Square edge -> ...
BTW, would it be possible (in principle) to allow constructor export 'read-only', so matching against a constructor is allowed but not constructing a value?
I don't see why not. To add something to the debate about what Circle /is/, I'd like to mention that the declaration data Shape = Circle Double | Square Double is a convenience that declares three new names (Shape, Circle and Square), but five entities. There's Shape: a type, Circle, Square:: Double -> Shape: constructor functions, and Circle, Square:: Shape -> (Double -> t) -> t -> t: destructor functions. The first three are available for general use by the programmer, but the last two are hidden in the works of pattern matching. I think this is what confuses things. In all contexts bar pattern matching and export lists, Circle and Square refer to the constructor functions (and they really are just functions in these contexts). In patterns they indirectly refer to the destructor functions, and in export lists to both. I'd like to see the separation made more accessible, and if this were done, one could export whatever combination of the entities one desired. I hesitate to raise the question of what syntax we might choose to represent this for fear of invoking Wadler's law. Jón -- Jón Fairbairn Jon.Fairbairn@cl.cam.ac.uk

On Monday 01 November 2004 22:34, you wrote:
On 2004-11-01 at 23:01+0100 Benjamin Franksen wrote:
On Monday 01 November 2004 21:51, Jon Fairbairn wrote:
Put the data declaration in a module, export the type, but
not the constructor you want to hide:
module Shape (Shape(Square), circle) where
Since we were talking about 'what can one do with a constructor as compared with a function', it should be mentioned that this also has a disadvantage: you loose pattern matching outside the module. I.e. no longer can say
... case x of Circle radius -> ... Square edge -> ...
BTW, would it be possible (in principle) to allow constructor export 'read-only', so matching against a constructor is allowed but not constructing a value?
I don't see why not. To add something to the debate about what Circle /is/, I'd like to mention that the declaration
data Shape = Circle Double | Square Double
is a convenience that declares three new names (Shape, Circle and Square), but five entities.
There's Shape: a type, Circle, Square:: Double -> Shape: constructor functions, and Circle, Square:: Shape -> (Double -> t) -> t -> t: destructor functions.
Interesting point of view! But... could you explain the types of the destructors? And how one would use them to deconstruct a Shape? Because, hmmm, isn't it rather *one* destructor with type destructShape :: Shape -> (Double -> t) -> (Double -> t) -> t where the second and third arguments explain what to do with a Circle resp. a Square? So that case s of Circle r -> f r Square l -> g l is another way to write destructShape s g f Ben

On 2004-11-02 at 00:11+0100 Benjamin Franksen wrote:
On Monday 01 November 2004 22:34, I wrote:
data Shape = Circle Double | Square Double
is a convenience that declares three new names (Shape, Circle and Square), but five entities.
There's Shape: a type, Circle, Square:: Double -> Shape: constructor functions, and Circle, Square:: Shape -> (Double -> t) -> t -> t: destructor functions.
Interesting point of view! But... could you explain the types of the destructors? And how one would use them to deconstruct a Shape? Because, hmmm, isn't it rather *one* destructor with type
destructShape :: Shape -> (Double -> t) -> (Double -> t) -> t
There could be, but that wouldn't suit my argument ;-)
where the second and third arguments explain what to do with a Circle resp. a Square? So that
case s of Circle r -> f r Square l -> g l
is another way to write
destructShape s g f
They amount to the same thing: if Circle.destruct:: Shape -> (Double -> t) -> t -> t and similarly Square.destruct, we'd just have to write the case as Circle.destruct s f (Square.destruct s g (error "impossible")) ie the .destructs take a Shape, a function to apply if it matches and a value to return if it doesn't. Apart from matching up with the names there's not much to choose between one destructor and many, except possibly when one considers something like: case e of Square s -> ... _ -> ... particularly if the type has more than two constructors. Jón -- Jón Fairbairn Jon.Fairbairn@cl.cam.ac.uk

On Monday 01 November 2004 23:40, Jon Fairbairn wrote:
if Circle.destruct:: Shape -> (Double -> t) -> t -> t and similarly Square.destruct, we'd just have to write the case as
Circle.destruct s f (Square.destruct s g (error "impossible"))
ie the .destructs take a Shape, a function to apply if it matches and a value to return if it doesn't.
Ah, I see. It's rather more ugly but it is a better match for what Haskell does at the moment, isn't it? (IIRC patterns are matched in the order they appear in the source).
Apart from matching up with the names there's not much to choose between one destructor and many, except possibly when one considers something like:
case e of Square s -> ... _ -> ...
particularly if the type has more than two constructors.
True. Anyway, we don't really want to abandon pattern matching syntax, do we? Ben

Benjamin Franksen writes:
On Monday 01 November 2004 23:40, Jon Fairbairn wrote:
Apart from matching up with the names there's not much to choose between one destructor and many, except possibly when one considers something like:
case e of Square s -> ... _ -> ...
particularly if the type has more than two constructors.
True. Anyway, we don't really want to abandon pattern matching syntax, do we?
Explicit destructor functions are nice when working in a point-free
fashion. Consider these:
c1 = someComputation >>= maybe mzero return
c2 = do
x <- someComputation
case x of
Just x' -> return x'
Nothing -> mzero
On the other hand, this function (which I actually have in my code) may
be over-doing it:
swap = maybe (Right Nothing) (either Left (Right . Just))
--
David Menendez

Just wanted to point out you can get accessor/deconstructor functions using record notation: data Shape = Circle { radius :: Double } | Square { length :: Double } Keean. Benjamin Franksen wrote:
On Monday 01 November 2004 22:34, you wrote:
On 2004-11-01 at 23:01+0100 Benjamin Franksen wrote:
On Monday 01 November 2004 21:51, Jon Fairbairn wrote:
Put the data declaration in a module, export the type, but
not the constructor you want to hide:
module Shape (Shape(Square), circle) where
Since we were talking about 'what can one do with a constructor as compared with a function', it should be mentioned that this also has a disadvantage: you loose pattern matching outside the module. I.e. no longer can say
... case x of Circle radius -> ... Square edge -> ...
BTW, would it be possible (in principle) to allow constructor export 'read-only', so matching against a constructor is allowed but not constructing a value?
I don't see why not. To add something to the debate about what Circle /is/, I'd like to mention that the declaration
data Shape = Circle Double | Square Double
is a convenience that declares three new names (Shape, Circle and Square), but five entities.
There's Shape: a type, Circle, Square:: Double -> Shape: constructor functions, and Circle, Square:: Shape -> (Double -> t) -> t -> t: destructor functions.
Interesting point of view! But... could you explain the types of the destructors? And how one would use them to deconstruct a Shape? Because, hmmm, isn't it rather *one* destructor with type
destructShape :: Shape -> (Double -> t) -> (Double -> t) -> t
where the second and third arguments explain what to do with a Circle resp. a Square? So that
case s of Circle r -> f r Square l -> g l
is another way to write
destructShape s g f
Ben _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Benjamin Franksen wrote:
Because, hmmm, isn't it rather *one* destructor with type
destructShape :: Shape -> (Double -> t) -> (Double -> t) -> t
where the second and third arguments explain what to do with a Circle resp. a Square? So that
case s of Circle r -> f r Square l -> g l
is another way to write
destructShape s g f
I can't resist pointing out that we don't even need destructShape, nor any internal representation of a Shape, because we can make the value itself the deconstructor: Circle :: Double -> (Double -> t) -> (Double -> t) -> t Circle d = \c s -> c d Square :: Double -> (Double -> t) -> (Double -> t) -> t Square d = \c s -> s d Every algebraic data type has a natural representation of this form. I used this idiom extensively in my Lazy K sample code [1] [2]. -- Ben [1] http://homepages.cwi.nl/~tromp/cl/lazy-k.html [2] http://esoteric.sange.fi/essie2/download/lazy-k/eg/

On Monday 01 November 2004 23:48, Ben Rudiak-Gould wrote:
Benjamin Franksen wrote:
Because, hmmm, isn't it rather *one* destructor with type
destructShape :: Shape -> (Double -> t) -> (Double -> t) -> t
where the second and third arguments explain what to do with a Circle
resp. a
Square? So that
case s of Circle r -> f r Square l -> g l
is another way to write
destructShape s g f
I can't resist pointing out that we don't even need destructShape, nor any internal representation of a Shape, because we can make the value itself the deconstructor:
Circle :: Double -> (Double -> t) -> (Double -> t) -> t Circle d = \c s -> c d
Square :: Double -> (Double -> t) -> (Double -> t) -> t Square d = \c s -> s d
Every algebraic data type has a natural representation of this form. I used this idiom extensively in my Lazy K sample code [1] [2].
Yes, i remember i have seen this technique mentioned before, i believe it was in Structure and Interpretation of Computer Programs. Ben PS: Lazy K is cool!

Put the data declaration in a module, export the type, but not the constructor you want to hide:
module Shape (Shape(Square), circle) where
Since we were talking about 'what can one do with a constructor as compared with a function', it should be mentioned that this also has a disadvantage: you loose pattern matching outside the module. I.e. no longer can say [..] BTW, would it be possible (in principle) to allow constructor export 'read-only', so matching against a constructor is allowed but not constructing a value?
OCaml has this:
http://caml.inria.fr/ocaml/htmlman/manual021.html#htoc99
--KW 8-)
--
Keith Wansbrough
participants (7)
-
Ben Rudiak-Gould
-
Benjamin Franksen
-
Brian Beckman
-
David Menendez
-
Jon Fairbairn
-
Keean Schupke
-
Keith Wansbrough