
Is there a Haskell analogue to OCaml's private types? In OCaml, you can do this (converting to pseudo-Haskell syntax): type T = private A Int Then, A cannot be used directly to construct values of type T. A 3 Error: Cannot create values of the private type T You must provide another constructor, makeT, which takes an Int and returns a T. This allows you to do additional checks on the Int argument. However, you can still deconstruct values of type T. f (A x) = x + 2 This works even when f is defined in a different module. The benefit is that you can restrict the allowed values of T, but still have the convenience of using existing operations on these values once constructed. The solution that comes to mind is to make T abstract and an instance of some appropriate class, but there is no class that lets you pattern match on arbitrary variant types.

Hi I don't think there is a direct equivalence. You can make T an opaque type using a module where you do not export the constructor. However, you can't then pattern match on the type so you have to supply a destructor - here called unT. Any module that imports XYZ only sees the type T, the 'handmade' constructor makeT and the destructor unT: module XYZ ( T, -- this does not export the constructor unT makeT ) where data T = PrivateT Int deriving (Eq,Show) unT :: T -> Int unT (PrivateT i) = i -- Add any checking you want here... makeT :: Int -> T makeT i = PrivateT i

This makes T fully abstract, which is what I'm trying to avoid. Private
types provide an intermediate level of abstraction. The real example I have
involves defining a type with numerous constructors (or a record with
numerous fields), and I'd like to avoid writing all the corresponding
destructors. Even if I did do this, it burdens clients of the module by
requiring them to use the alternative destructors.
I think the feature I'm looking for is "guarded constructors", but to my
knowledge there is no such thing.
On Thu, Apr 8, 2010 at 3:42 PM, Stephen Tetley
Hi
I don't think there is a direct equivalence. You can make T an opaque type using a module where you do not export the constructor. However, you can't then pattern match on the type so you have to supply a destructor - here called unT. Any module that imports XYZ only sees the type T, the 'handmade' constructor makeT and the destructor unT:
module XYZ ( T, -- this does not export the constructor unT makeT
) where
data T = PrivateT Int deriving (Eq,Show)
unT :: T -> Int unT (PrivateT i) = i
-- Add any checking you want here... makeT :: Int -> T makeT i = PrivateT i

A variant on Stephen's solution is to use Haskell's record syntax, which
will generate the "destructors" implicitly. This is no easier on your
users, but much easier for you to write, depending on the structure of your
type.
On Thu, Apr 8, 2010 at 15:54, Ashish Agarwal
This makes T fully abstract, which is what I'm trying to avoid. Private types provide an intermediate level of abstraction. The real example I have involves defining a type with numerous constructors (or a record with numerous fields), and I'd like to avoid writing all the corresponding destructors. Even if I did do this, it burdens clients of the module by requiring them to use the alternative destructors.
I think the feature I'm looking for is "guarded constructors", but to my knowledge there is no such thing.
On Thu, Apr 8, 2010 at 3:42 PM, Stephen Tetley
wrote: Hi
I don't think there is a direct equivalence. You can make T an opaque type using a module where you do not export the constructor. However, you can't then pattern match on the type so you have to supply a destructor - here called unT. Any module that imports XYZ only sees the type T, the 'handmade' constructor makeT and the destructor unT:
module XYZ ( T, -- this does not export the constructor unT makeT
) where
data T = PrivateT Int deriving (Eq,Show)
unT :: T -> Int unT (PrivateT i) = i
-- Add any checking you want here... makeT :: Int -> T makeT i = PrivateT i
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
-- mac

The GHC extension "view patterns" does roughly what you want. See here: http://hackage.haskell.org/trac/ghc/wiki/ViewPatterns Ashish Agarwal wrote:
Is there a Haskell analogue to OCaml's private types? In OCaml, you can do this (converting to pseudo-Haskell syntax):
type T = private A Int
Then, A cannot be used directly to construct values of type T. A 3 Error: Cannot create values of the private type T
You must provide another constructor, makeT, which takes an Int and returns a T. This allows you to do additional checks on the Int argument. However, you can still deconstruct values of type T.
f (A x) = x + 2
This works even when f is defined in a different module. The benefit is that you can restrict the allowed values of T, but still have the convenience of using existing operations on these values once constructed.
The solution that comes to mind is to make T abstract and an instance of some appropriate class, but there is no class that lets you pattern match on arbitrary variant types.
------------------------------------------------------------------------
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

Hi Dominic
They can get a bit closer but (I think) you would still need to define
a auxiliary view type that exports its constructor:
module View1 (
T, -- opaque
TView(..), -- not opaque
tview,
mkT
)
where
data T = PrivateT Int deriving (Eq,Show)
-- auxillary type
data TView = TView Int deriving (Eq,Show)
tview :: T -> TView
tview (PrivateT i) = TView i
mkT :: Int -> T
mkT i = PrivateT i
-- client module with views (new file) :
{-# LANGUAGE ViewPatterns #-}
module UseView where
import View1
-- Use the view pattern:
add1 :: T -> T
add1 (tview -> TView i) = mkT (i+1)
-- or long hand...
add1_alt :: T -> T
add1_alt t = case tview t of
TView i -> mkT i
On 8 April 2010 21:35, Dominic Mulligan
The GHC extension "view patterns" does roughly what you want.
See here: http://hackage.haskell.org/trac/ghc/wiki/ViewPatterns
Ashish Agarwal wrote:
Is there a Haskell analogue to OCaml's private types? In OCaml, you can do this (converting to pseudo-Haskell syntax):
type T = private A Int
Then, A cannot be used directly to construct values of type T. A 3 Error: Cannot create values of the private type T
You must provide another constructor, makeT, which takes an Int and returns a T. This allows you to do additional checks on the Int argument. However, you can still deconstruct values of type T.
f (A x) = x + 2
This works even when f is defined in a different module. The benefit is that you can restrict the allowed values of T, but still have the convenience of using existing operations on these values once constructed.
The solution that comes to mind is to make T abstract and an instance of some appropriate class, but there is no class that lets you pattern match on arbitrary variant types.
------------------------------------------------------------------------
_______________________________________________ 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

Hi Stephen, Yes, that is correct. But I don't see why this matters (unless I'm missing something obvious?). In this case, you cannot construct a value of type T using TView's constructors, and presumably all the functions defined in module View1 will be defined over T, not TView. If the question was to find a perfect analogue to O'Caml's private types, then probably one doesn't exist, but GHC's view patterns are the closest Haskell feature that does the intended purpose of allowing pattern matching without breaking abstraction (that I'm aware of, of course :)). Stephen Tetley wrote:
Hi Dominic
They can get a bit closer but (I think) you would still need to define a auxiliary view type that exports its constructor:
module View1 ( T, -- opaque TView(..), -- not opaque tview, mkT ) where
data T = PrivateT Int deriving (Eq,Show)
-- auxillary type data TView = TView Int deriving (Eq,Show)
tview :: T -> TView tview (PrivateT i) = TView i
mkT :: Int -> T mkT i = PrivateT i
-- client module with views (new file) :
{-# LANGUAGE ViewPatterns #-}
module UseView where
import View1
-- Use the view pattern: add1 :: T -> T add1 (tview -> TView i) = mkT (i+1)
-- or long hand... add1_alt :: T -> T add1_alt t = case tview t of TView i -> mkT i
On 8 April 2010 21:35, Dominic Mulligan
wrote: The GHC extension "view patterns" does roughly what you want.
See here: http://hackage.haskell.org/trac/ghc/wiki/ViewPatterns
Ashish Agarwal wrote:
Is there a Haskell analogue to OCaml's private types? In OCaml, you can do this (converting to pseudo-Haskell syntax):
type T = private A Int
Then, A cannot be used directly to construct values of type T. A 3 Error: Cannot create values of the private type T
You must provide another constructor, makeT, which takes an Int and returns a T. This allows you to do additional checks on the Int argument. However, you can still deconstruct values of type T.
f (A x) = x + 2
This works even when f is defined in a different module. The benefit is that you can restrict the allowed values of T, but still have the convenience of using existing operations on these values once constructed.
The solution that comes to mind is to make T abstract and an instance of some appropriate class, but there is no class that lets you pattern match on arbitrary variant types.
------------------------------------------------------------------------
_______________________________________________ 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
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

Thanks for all the suggestions. I also see that Haskell allows the same record field name in multiple constructors. This also helps for the type definition I had in mind: module XYZ ( T(foo,bar), makeA, makeB ) where data T = PrivateA { foo :: Int } | PrivateB { foo :: Int, bar :: Int } deriving (Eq,Show) makeA :: Int -> T makeA i = PrivateA {foo=i} makeB :: Int -> Int -> T makeB i j = PrivateB {foo=i, bar=j} On Thu, Apr 8, 2010 at 5:27 PM, Dominic Mulligan < dominic.p.mulligan@googlemail.com> wrote:
Hi Stephen,
Yes, that is correct. But I don't see why this matters (unless I'm missing something obvious?). In this case, you cannot construct a value of type T using TView's constructors, and presumably all the functions defined in module View1 will be defined over T, not TView. If the question was to find a perfect analogue to O'Caml's private types, then probably one doesn't exist, but GHC's view patterns are the closest Haskell feature that does the intended purpose of allowing pattern matching without breaking abstraction (that I'm aware of, of course :)).
Stephen Tetley wrote:
Hi Dominic
They can get a bit closer but (I think) you would still need to define a auxiliary view type that exports its constructor:
module View1 ( T, -- opaque TView(..), -- not opaque tview, mkT ) where
data T = PrivateT Int deriving (Eq,Show)
-- auxillary type data TView = TView Int deriving (Eq,Show)
tview :: T -> TView tview (PrivateT i) = TView i
mkT :: Int -> T mkT i = PrivateT i
-- client module with views (new file) :
{-# LANGUAGE ViewPatterns #-}
module UseView where
import View1
-- Use the view pattern: add1 :: T -> T add1 (tview -> TView i) = mkT (i+1)
-- or long hand... add1_alt :: T -> T add1_alt t = case tview t of TView i -> mkT i
On 8 April 2010 21:35, Dominic Mulligan
wrote: The GHC extension "view patterns" does roughly what you want.
See here: http://hackage.haskell.org/trac/ghc/wiki/ViewPatterns
Ashish Agarwal wrote:
Is there a Haskell analogue to OCaml's private types? In OCaml, you can do this (converting to pseudo-Haskell syntax):
type T = private A Int
Then, A cannot be used directly to construct values of type T. A 3 Error: Cannot create values of the private type T
You must provide another constructor, makeT, which takes an Int and returns a T. This allows you to do additional checks on the Int argument. However, you can still deconstruct values of type T.
f (A x) = x + 2
This works even when f is defined in a different module. The benefit is that you can restrict the allowed values of T, but still have the convenience of using existing operations on these values once constructed.
The solution that comes to mind is to make T abstract and an instance of some appropriate class, but there is no class that lets you pattern match on arbitrary variant types.
------------------------------------------------------------------------
_______________________________________________ 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
_______________________________________________ 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
participants (4)
-
Ashish Agarwal
-
Dominic Mulligan
-
matthew coolbeth
-
Stephen Tetley