to all: excuse my bad english.
to javas: excuse my extreme opinions. - regard me as s.o. of an other... religion.
to newbies: read it.
to haskellers: you don't need to.

johi, Sean.

i remember that i've had the same problems with haskell, at the beginning.
you are right, that there should be a special introduction just for 
imperative-programmers.
but you are wrong, not haskell has to change sth. - the other languages have to do it, 
if anyone at all. but if the others are imperative languages, like all those you 
learned before, the change would imply to nullify their existence. ;)

> asm to forth to basic, pascal, C, C++, java, and C#...
i've learned the following:
MS-DOS-3.3/5.0 .bat files
QBASIC
QUICKBASIC
turbo-pascal + intel-asm
delphi
vc++ (while my university was/is_still teaching java like bill gates foists windows)
aversed look at java - whatabullshit!!! (all the extremest down running prejudices 
-not knowing the language- seem to fit -especially after having learned the language-. 
the power of half-oop, easy to learn like risc-asm, with the speed of basic, and the 
no-compiletime-but-runtime-typechecking of cLisp or Tcl. but as a psychology student 
i'm fascinated about those obvious marketing-tricks, making s.o. believe in java.)
cLisp
haskell
little bit prolog
vc++
haskell
vc++<stl>
linux :) :) :) :)
Tcl/Tk
haskell
c++<stl>
math (!!!best!!! - but not a computer language)
...

so i know those cut and dried opinions one has by learning new languages.
i've learned that there are at least two types of languages: the lower (->asm) and the 
higher (->math) ones.
in c++ the difference between "struct" and "class" is that its default is "public" or 
"private". that has nearly nothing to do with classes - except oop.
if you have data somewhere in memory, you call it an "instance" of a (struct- or 
class- or whatever-) type.
in math you have types, sets, elements, classes, instances, ... (but not "interface" - 
don't think in java. a human-machine interface like monitor+keyboard+mouse is an 
interface, too. to define an interface does mean to use a pattern, not an special 
abstract-only--no-variable--no-default-functionimplementation--java-class to simulate 
cumbersomely multi-inheritance.)
the language haskell is an attempt to implement math as computer language. (Haskell 
Brooks Curry was a genius who invented the banal function we call "curry".)
any function has a type; the data in your memory has a type; combinations of functions 
and data_structures_in_memory have types.
but a function is not a variable piece of memory - it depends on its definition, like 
a constant.
the types of data structures, which are "instanciated" in memory, are defined with 
that data keyword in haskell.

all types - functions too - are instances of classes; means: types are 
elements(instances) in special sets(classes), for which some individual attributes (in 
haskell: individual function-implementations) are defined.
try to proof this view in haskell and c++. you will see, that the sense of oop-classes 
is not the definition of types but the unification of inherited types.


some examples in c++ (didn't try to compile it):

template<typename a>
class Eq
{
protected:
        Eq(){} // This constructor exists just to be protected.
public:
        virtual bool operator ==( const a& r ) const {return !( (*this) != r );}
        virtual bool operator !=( const a& r ) const {return !( (*this) == r );}
};

template<typename a>
struct Maybe : public virtual Eq<Maybe<a> >
{
        enum Constructor_t {Nothing, Just};
        union{
                struct{
                        Constructor constructor_;
                };
                struct{
                        Constructor constructorNothing;
                };
                struct{
                        Constructor constructorJust;
                        const a *data;
                };
        };

        Maybe() { constructorNothing = Nothing; }
        Maybe(const a& d) { constructorJust = Just; data = new a(d); }
        Maybe(const Maybe& m) { constructor_ = m.constructor_; 
if(m.constructorJust==Just) data = new a(*m.data); }
        ~Maybe() { if( constructorJust == Just ) delete data; }

        virtual bool operator ==( const Maybe& r ) const
        {
                switch( constructor_ )
                {
                        case Nothing:
                                return (r.constructorNothing==Nothing);
                        case Just:
                                return (r.constructorJust !=Just) ? (false) : 
(*data==*r.data);
                }
                throw "undefined";
        }
};


// functionname :: (Eq a) => a -> returntype
template<typename a>
inline returntype functionname( const a& param )
{
        static_cast<const Eq<a>*>(&param); // ignore result of casting, but test 
wether...  param is instance / a (TYPE of param) is instance ...of Eq class.
        ...
}



merry xmas,
- marc





Am Mittwoch, 24. Dezember 2003 02:29 schrieb Sean L. Palmer:
> It occurs to me that Haskell would be quite a bit easier for OO and traditional 
> programmers to grasp if Haskell would actually use the correct, or at least more 
> commonly used, names for things.
> 
> For instance, 
> 
> data Maybe a = Nothing | Just a
> 
> Maybe is a type constructor and Nothing and Just are data constructors.
> 
> So it makes me wonder why the use of the data keyword... wouldn't it make more sense 
> to say: 
> 
> type Maybe a = Nothing | Just a
> 
> ?  Either that or perhaps change the descriptions "type constructor" and "data 
> constructor" to something that fits with the keywords used.  
> 
> Likewise with class, type class, and instance:
> 
> class Eq a where
>         (==) :: a -> a -> Bool
> 
> That actually declares a type class, not a class.  So why the use of the keyword 
> class?  Is it done merely to confuse C++ and Java programmers?  The concept of type 
> class in Haskell apparently roughly corresponds to the concept of "interface" in 
> Java.  So why not call it interface?  
> 
> Instance is also confusing:
> 
> instance Eq Integer where 
>   a == b = a `integerEq` b
> 
> That actually declares that Integer is a type, not an "instance" in the traditional 
> use of the word.  A C++ programmer would probably use the word "subclass" instead of 
> "instance".
> 
> Then consider how different a meaning "return" has in Haskell than it does in C.   ;)
> 
> Does anyone else think this is a problem?  If so, is it fixable?
> 
> I guess from reading the many tutorials and FAQ's, that I'm in the same boat as 
> everybody else.  I consider myself a pretty bright boy, I've learned all kinds of 
> other programming languages, from asm to forth to basic, pascal, C, C++, java, and 
> C#...  but this Haskell business, has me almost stumped.  I mean, I understand the 
> basic ideas pretty easily enough, but there seems to be such syntactical wierdness 
> that to understand how to program in Haskell above the level of toy programs 
> requires one to revisit every single design decision that went into making the 
> language and its libraries, and grasp everything along the way, not only its 
> function but also its peculiar nomenclature, and usually two different ways to say 
> the same thing (maybe more).  Only after following this long tortuous path will one 
> ever be able to actually write useful programs.  
> 
> If Haskell (or any language of this style) is ever to gain a larger following, it 
> would probably be wise to accomodate the existing programmer knowledge base a little 
> more.  I believe that the same core language, with cleaner design, different 
> keywords, maybe different operators, would probably be readily accepted.  
> 
> There are many things that contribute to making Haskell less approachable, the above 
> is just one.
> 
> I wonder if there are any tutorials out there that provide a 1:1 mapping of concepts 
> and idioms from other common languages into Haskell; small snippets of examples of 
> pure translations would make things easier to grasp for some people than any amount 
> of longwinded explanation.  Probably there are easier ways to do the same things in 
> Haskell, but it would be useful for beginners to get a unedited translation, even if 
> that means heavy use of do-notation.  At least people could then start writing 
> imperative style Haskell programs immediately, and yeah that's not good style, but 
> you can't learn good style if you can't accomplish anything and are stuck at square 
> one.
> 
> Frustratedly,
> Sean
> 

_______________________________________________
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell

Reply via email to