The thing is, that one ALWAYS wants to create a union of types, and not
merely an ad-hock list of data declarations.  So why does it take more code
to do "the right thing(tm)" than to do "the wrong thing(r)"?  Lets take an
example from Conor McBride's "she"  https://github.com/timthelion/her-lexer/
blob/master/src/Language/Haskell/Her/HaLay.lhs#L139  Line 139 we have a case
statement:

>        ((i, t) : its') -> case (m, t) of
>          (Lay _ j, _) | not (null acc) && i <= j -> (reverse acc, its)
>          (Lay _ _, Semi) -> (reverse acc, its)
>          (Lay k _, KW e) | elem (k, e) layDKillaz -> (reverse acc, its)
>          (Lay _ _, Clo _) -> (reverse acc, its)
>          (Bra b, Clo b') | b == b' -> (reverse acss, its')
>          (m, Ope b) -> case getChunks (Bra b) [] its' of
>            (cs, its) -> getChunks m (B b cs : acss) its
>          (m, KW e) | elem e lakeys -> case getLines (Seek m e) [] its' of
>            (css, its) -> getChunks m ((L e css) : acss) its
>          _ -> getChunks m (t : acss) its'

Maybe we would want to re-factor this like so:

>        ((i, t) : its') -> case (m, t) of
>          layTup@(Lay{}, _) | layTest layTup -> (reverse acc, its)
>          (Bra b, Clo b') | b == b' -> (reverse acss, its')
>          (m, Ope b) -> case getChunks (Bra b) [] its' of
>            (cs, its) -> getChunks m (B b cs : acss) its
>          (m, KW e) | elem e lakeys -> case getLines (Seek m e) [] its' of
>            (css, its) -> getChunks m ((L e css) : acss) its
>          _ -> getChunks m (t : acss) its'

>    where
>     layTest :: (ChunkMode,Tok) -> Bool
>     layTest (Lay _ j, _) | not (null acc) && i <= j = True
>     layTest (Lay _ _, Semi) = True
>     layTest (Lay k _, KW e) | elem (k, e) layDKillaz = True
>     layTest (Lay _ _, Clo _) = True
>     layTest _ = False

You see what's wrong with layTest's type?  It shouldn't be taking a 
(ChunkMode,Tok) but rather a (Lay,Tok).  You ALWAYS run into this.  Perhaps
you would understand the problem better, if I hadn't said that the data
union of types is too ugly, but that the normal data is too pretty?  
Everyone ends up getting caught in this trap.  And the only way out is to re
-write your code with better typing.

Timothy


Od: Tim Docker <t...@dockerz.net>
Datum: 2. 9. 2012
Předmět: Re: [Haskell-cafe] Over general types are too easy to make.
---------- Původní zpráva ----------
"On 01/09/12 04:00, timothyho...@seznam.cz wrote:
> I'd have to say that there is one(and only one) issue in Haskell that
> bugs me to the point where I start to think it's a design flaw:
>
> It's much easier to type things over generally than it is to type
> things correctly.
>
> Say we have a
>
> >data BadFoo =
> > BadBar{
> > badFoo::Int} |
> > BadFrog{
> > badFrog::String,
> > badChicken::Int}
>
> This is fine, until we want to write a function that acts on Frogs but 
> not on Bars. The best we can do is throw a runtime error when passed
> a Bar and not a Foo:
>
> >deBadFrog :: BadFoo -> String
> >deBadFrog (BadFrog s _) = s
> >deBadFrog BadBar{} = error "Error: This is not a frog."
>
> We cannot type our function such that it only takes Frogs and not
> Bars. This makes what should be a trivial compile time error into a
> nasty runtime one :(
>
> The only solution I have found to this is a rather ugly one:
>
> >data Foo = Bar BarT | Frog FrogT
>
> If I then create new types for each data constructor.
>
> >data FrogT = FrogT{
> > frog::String,
> > chicken::Int}
>
> >data BarT = BarT{
> > foo :: Int}
>
> Then I can type deFrog correctly.
>
> >deFrog :: FrogT -> String
> >deFrog (FrogT s _) = s
>

I'm curious as to what you find ugly about this. It appears you need to
distinguish between Bars and Frogs, so making them separate types (and
having a 3rd type representing the union) is a natural haskell solution:

data Bar = ..
data Frog = ..

fn1 :: Bar -> ..
fn2 :: Frog -> ..
fn3 :: Either Bar Frog -> ..

Perhaps a more concrete example would better illustrate your problem?

Tim





_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
(http://www.haskell.org/mailman/listinfo/haskell-cafe)"
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to