[Haskell] monads, records, verbosity
S. Alexander Jacobson
alex at alexjacobson.com
Thu Jan 5 14:14:12 EST 2006
Much of the discussion here recently has been related to debate about
complexifying the monad hierarchy. The fact that Haskell record
syntax is abysmal and the verbosity of various possible solutions.
They appear to interrelate.
Would it be possible/reasonable to get rid of data, class, and
instance declarations and rely on type inference for everything?
Here is my strawman version:
* functions definitions imply the data declarations required
foo True = Just "abc"
foo False = Nothing
==implies==>
data A1 = True | False
data A2 a = Just a | Nothing
* all function definitions are actually instance declarations of an
implicit class that implements that function so e.g.
foo True = Just "abc"
foo False = Nothing
==implies==>
class Foo a b where foo::a->b
instance Foo A1 A2 where
foo True = Just "abc"
foo False = Nothing
* multiple definitions of the same function imply distinct instance
declarations:
foo 0 = Nothing
foo x = Just (x+1)
==implies ==>
class Foo a b where foo::a->b -- same as above definition of Foo
instance Foo A1 (A2 A1) where .....
* field labels happen in context
mkPot = Pot {profit=0,amounts=[]}
updatePot p = p {profit \= (1+),amount \= (1:)}
getProfit p = profit p
== implies ==>
data A3 = Pot Int [Int]
class Profit a where profit::a->Int
class Amounts a where amounts::a->[Int]
instance Profit A3 where profit (Pot a _)=a
instance Amounts A3 where amounts (Pot _ a)=a
class UpdatePot a where updatePot::a->a
instance UpdatePot A3 where updatePot (Pot a b) = Pot (1+a) (1:b)
getProfit p = profit p
* default instances are as follows
foo a b c = b -- the default instance
foo (a::Pot) b c = c -- the specialized instance
Is this possible/reasonable?
-Alex-
______________________________________________________________
S. Alexander Jacobson tel:917-770-6565 http://alexjacobson.com
More information about the Haskell
mailing list