[Haskell-cafe] data types with overlapping component names (in one module)?

Sturdy, Ian sturdyi12 at mail.wlu.edu
Wed Apr 17 21:09:23 CEST 2013


True, and thank you for clarifying that. I was thinking of the names of the field data, not the type-level name of the field:

name = Field :: "name" ::: String

-IRS
________________________________________
From: acowley at gmail.com [acowley at gmail.com] on behalf of Anthony Cowley [acowley at seas.upenn.edu]
Sent: Tuesday, April 16, 2013 6:13 PM
To: Sturdy, Ian
Cc: haskell-cafe at haskell.org
Subject: Re: [Haskell-cafe] data types with overlapping component names (in one module)?

On Tue, Apr 16, 2013 at 4:05 PM, Sturdy, Ian <sturdyi12 at mail.wlu.edu> wrote:
> 'vinyl' uses type-level literal strings and is very slick (although all fields with the same name have the same type)

This is not entirely true, depending on what you mean by "name". The
following is just fine. You only have naming issues if you want to
give @Field::"baz":::Int@ a name, that name is, unsurprisingly, tied
to the field type of Int.

{-# LANGUAGE DataKinds, TypeOperators #-}
import Data.Vinyl

type Foo = '["baz" ::: Int]
type Bar = '["baz" ::: String]

x :: PlainRec Foo
x = Field =: 2

y :: PlainRec Bar
y = Field =: "Two"


Anthony

>
> -IRS
> ________________________________________
> From: haskell-cafe-bounces at haskell.org [haskell-cafe-bounces at haskell.org] on behalf of Johannes Waldmann [waldmann at imn.htwk-leipzig.de]
> Sent: Tuesday, April 16, 2013 8:17 AM
> To: haskell-cafe at haskell.org
> Subject: [Haskell-cafe] data types with overlapping component names (in one     module)?
>
> What is the current situation: can we have two types
> with overlapping component names in one module?
>
> module M where
> data T1 = C1 { foo :: Int }
> data T2 = C2 { foo :: String }
>
> It seems not (ghc says: Multiple declarations of 'foo'). This comes close:
> http://www.haskell.org/ghc/docs/7.6.2/html/users_guide/syntax-extns.html#disambiguate-fields
> but still requires the definitions to reside in different modules?
>
> This is a major pain (it forces me to spread the source over several files),
> and also a show-stopper when selling Haskell to OO folks, who "naturally"
> assume that a class also denotes a scope. (And that you could nest them.)
>
> Are/were there plans/proposals to address this?
>
> - J.W.
>
>
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe





More information about the Haskell-Cafe mailing list