[Haskell-beginners] private types

Stephen Tetley stephen.tetley at gmail.com
Thu Apr 8 17:10:36 EDT 2010


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
<dominic.p.mulligan at googlemail.com> 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 at haskell.org
>> http://www.haskell.org/mailman/listinfo/beginners
>>
>
> _______________________________________________
> Beginners mailing list
> Beginners at haskell.org
> http://www.haskell.org/mailman/listinfo/beginners
>


More information about the Beginners mailing list