[Haskell-cafe] Abstract Data Types

Robert Dockins robdockins at fastmail.fm
Wed Aug 9 09:05:20 EDT 2006


On Aug 9, 2006, at 5:27 AM, Johan Grönqvist wrote:

> Hi,
>
> I have a question:
>
> Short version: If I want to hide the implementation of a data-type  
> "Stack a" from the rest of the program,  do I need to put its  
> definition in a separate file?
>

This is the usual way, as you've probably gathered.

>
> Long version:
>
> I want to use a stack, and I might implement it as a list, but I  
> want to hide the implementation from the rest of the program. This  
> is how I understand abstract data type.
>
> In "The Craft of Functional Programming", this seems to be  
> implemented by putting each data type into a separate module and  
> only exporting parts of the definitions.
>
> In "The Haskell School of Expression", this seems not to be used at  
> all.
>
> In the lecture notes at (http://www.dcs.shef.ac.uk/~mps/courses/ 
> com2020/adts.pdf), type classes are used for abstract data types.  
> It seems to me that this approach does not hide any parts of any  
> definition, but only requires that all instances of class stack  
> have functions pop and push of the correct types. I am interested  
> in hiding parts of definitions.
>
> In the report, I did not find any mention of a requirement to have  
> different modules in separate files, but I have not managed to put  
> several modules in the same file using ghci.


I think all current implementations require separate files for  
separate modules, although I believe you are correct that is is not  
required by the report.


> I would like to keep my small program in one literate-haskell tex- 
> file and still be able to hide some definitions from others.
>
> Is this possible?
>
> One option would of course be to write a script that separates the  
> code into different and then compiles the entire program.



There are two other basic ways that I know of to achieve data type  
abstraction.


1) Parametric polymorphism

Create a typeclass with the appropriate operations.  Then, in  
functions which use stack operations, always write, eg:


doSomething :: Stack s => s a -> Bool

rather than

doSomething :: ConcreteStackType a -> Bool



This is abstraction "at the point of use" if you will.  You'll see  
this technique pretty often used to abstract over different Monads,  
for example.



2) Exestential datatypes.  You can create a sort of poor-man's  
substitute for ML style module systems by using existential data  
types.  Its a little fiddly, but it mostly works:


{-# OPTIONS -fglasgow-exts #-}

import Data.Maybe (isJust)


data StackRec a = forall s. Show (s a) => StackRec (s a) (a -> s a ->  
s a) (s a -> s a) (s a -> Maybe a)
listStackRec =
    StackRec
       []
       (:)
       (\xs -> case xs of (_:ys) -> ys; [] -> [])
       (\xs -> case xs of (y:_) -> Just y; [] -> Nothing)


fauxModule :: IO ()
fauxModule =
   case listStackRec of { StackRec empty push pop peek -> do

         print (isJust (peek (pop (pop (push 'a' empty)))))
         print (push 'b' empty)

         -- doesn't typecheck
         --print (push 'c' [])

   }

main = fauxModule




Unfortunately, the case statement gives you monomorphic bindings for  
the stack methods, and let bindings don't play nice with  
existentials.  I'm not sure if there's a way around this or not.


> Thanks in advance!
>
> / johan grönqvist


Rob Dockins

Speak softly and drive a Sherman tank.
Laugh hard; it's a long way to the bank.
           -- TMBG





More information about the Haskell-Cafe mailing list