Re: [Haskell-cafe] testing for same characters in lists of strings

2008-04-07 Thread Henning Thielemann
On Mon, 7 Apr 2008, Jackm139 wrote: I'm new to Haskell, and I'm finding it is very different from any other language I have worked with. I have an assignment to make a program to test whether two lists use the same characters for each string. e.g. sameCharacter ["rock", "cab"] ["cork", "abc"

Re: [Haskell-cafe] Re: type families and type signatures

2008-04-07 Thread Manuel M T Chakravarty
apfelmus: Manuel M T Chakravarty wrote: Ganesh Sittampalam: Let's alpha-rename the signatures and use explicit foralls for clarity: foo :: forall a. Id a -> Id a foo' :: forall b. Id b -> Id b GHC will try to match (Id a) against (Id b). As Id is a type synonym family, it would *not* be

Re: [Haskell-cafe] Re: type families and type signatures

2008-04-07 Thread Manuel M T Chakravarty
Hi Mark, I don't know if you have defined/studied corresponding notions of ambiguity/coherence in your framework. Instead, I was referring to what Manuel described as "the equivalent problem using FDs": class IdC a b | a -> b instance IdC Int Int bar :: IdC a b => b -> b bar = id bar' :

Re: [Haskell-cafe] testing for same characters in lists of strings

2008-04-07 Thread Dan Weston
I don't know how to calibrate my response to what you are really asking for. Depending on how "new" you are, maybe all you want is just "working syntax" to get you started. Here is a structurally similar problem, if it helps. (And if you are more advanced, try the extra credit!) Find the "ave

Re: [Haskell-cafe] translating from fundeps into type families

2008-04-07 Thread Manuel M T Chakravarty
Ganesh Sittampalam: Can I have some advice on translating the attached Test1.hs into type families? My attempt at doing so is in Test1a.hs, but firstly it requires FlexibleInstances where Test1.hs didn't, and secondly it fails because it can't infer the instance for Bar (Either Int Int) wh

Re: [Haskell-cafe] testing for same characters in lists of strings

2008-04-07 Thread Stuart Cook
On Tue, Apr 8, 2008 at 1:51 PM, Jackm139 <[EMAIL PROTECTED]> wrote: > I have an assignment to make a program to test whether two lists use the > same characters for each string. > e.g. > > sameCharacter ["rock", "cab"] ["cork", "abc"] > True I would start with something smaller: try defining

Re: [Haskell-cafe] testing for same characters in lists of strings

2008-04-07 Thread Krzysztof Kościuszkiewicz
On Mon, Apr 07, 2008 at 07:51:05PM -0700, Jackm139 wrote: > I have an assignment to make a program to test whether two lists use the > same characters for each string. > e.g. > > sameCharacter ["rock", "cab"] ["cork", "abc"] > True > > My plan to tackle this was to use: > nub to eliminate duplic

[Haskell-cafe] testing for same characters in lists of strings

2008-04-07 Thread Jackm139
I'm new to Haskell, and I'm finding it is very different from any other language I have worked with. I have an assignment to make a program to test whether two lists use the same characters for each string. e.g. sameCharacter ["rock", "cab"] ["cork", "abc"] True My plan to tackle this was to us

Re: [Haskell-cafe] Problem building HXT

2008-04-07 Thread gwern0
On 2008.04.07 20:17:06 +0200, ln <[EMAIL PROTECTED]> scribbled 1.1K characters: > Hi, > > I would like to try HXT, but I can't manage to build it. I resolved all > the dependencies, but I get the following error: > > > > [EMAIL PROTECTED]:~/Desktop/hxt$ make all > > > make -C src all VERSION=7

Re: [Haskell-cafe] problems building hpodder

2008-04-07 Thread John Goerzen
On Monday 07 April 2008 5:57:39 pm [EMAIL PROTECTED] wrote: > So almost certainly the issue is that HaXml has updated and changed things > around in a way that broke Hpodder; not surprising, since HaXml-1.19.2 is > as recent as 14 January 2008, and Goerzen may simply not have updated and > discove

Re: [Haskell-cafe] Type Families: infinite compile process?

2008-04-07 Thread Ryan Ingram
Actually, this even works without undecidable instances! On 4/7/08, Ryan Ingram <[EMAIL PROTECTED]> wrote: > {-# OPTIONS -fglasgow-exts -fallow-undecidable-instances #-} ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailma

Re: [Haskell-cafe] Type Families: infinite compile process?

2008-04-07 Thread Ryan Ingram
The type system requires strong normalization. By specifying "allow-undecidable-instances", you are agreeing to provide proofs of strong normalization outside of the compiler, instead of relying on the compiler to derive them for you. Because you have claimed that your instance is strongly normal

Re: [Haskell-cafe] deriving

2008-04-07 Thread PR Stanley
Hi, Thank you very much for your helpful replies. So, we define (or is it declare) a class with a polymorphic value(s which will be used in defining function types or functions associated with that class. The data types are then used for deriving instances of that class specific to each data ty

Re: [Haskell-cafe] problems building hpodder

2008-04-07 Thread gwern0
On 2008.04.07 00:24:10 +0200, Karl Hasselström <[EMAIL PROTECTED]> scribbled 0.9K characters: > I'm trying to build hpodder 1.1.2 with ghc 6.8.2. I successfully > downloaded, built, and installed (the latest versions of) all its > dependencies, but when building hpodder itself, I get > > FeedParse

Re[2]: [Haskell-cafe] deriving

2008-04-07 Thread Bulat Ziganshin
Hello Hans, Tuesday, April 8, 2008, 2:28:53 AM, you wrote: > At least Hugs complains if one does not indent "deriving ...", but I > do not know what the standard says. If is required, then it can be > changed. deriving is a part of data clause and indentation just allows us to continue clause

Re: [Haskell-cafe] deriving

2008-04-07 Thread Hans Aberg
On 7 Apr 2008, at 21:48, Brandon S. Allbery KF8NH wrote: But here, one would have to think about how the compiler should be able to distinguish data Bool = False | True instance (Eq) from data Bool = False | True instance Eq Bool where x == y = ... Layout already does that, doe

Re: [Haskell-cafe] Re: type families and type signatures

2008-04-07 Thread Mark P Jones
Hi Tom, It seems we are thinking of different things. I was referring to the characterization of a type of the form P => t as being "ambiguous" if there is a type variable in P that is not determined by the variables in t; this condition is used in Haskell to establish coherence (i.e., to show t

[Haskell-cafe] Re: Type Families: infinite compile process?

2008-04-07 Thread Hugo Pacheco
The problem is that the representation probably does not reduce to a normal form. Say, for the case type instance F (Nest a) x = Either() (a,F a x) fnn :: F (Nest a) (Nest a) fnn = Left () it compiles ok. But why can't the representation be infinite, like any other infinite data type? Cheers, h

[Haskell-cafe] Type Families: infinite compile process?

2008-04-07 Thread Hugo Pacheco
Hi guys, I have been experimenting some weird stuff (risky, yes I know) but the behaviour was certainly not the one I expected: {-# OPTIONS -fglasgow-exts -fallow-undecidable-instances #-} module Nest where data Nest a = Nil | Cons a (Nest (a,a)) type family F a x :: * type instance F (Nest a)

[Haskell-cafe] translating from fundeps into type families

2008-04-07 Thread Ganesh Sittampalam
Hi, Can I have some advice on translating the attached Test1.hs into type families? My attempt at doing so is in Test1a.hs, but firstly it requires FlexibleInstances where Test1.hs didn't, and secondly it fails because it can't infer the instance for Bar (Either Int Int) whereas the fundeps v

[Haskell-cafe] Re: type families and type signatures

2008-04-07 Thread Stefan Monnier
> Id is an operation over types yielding a type, as such it doesn't make > much sense to me to have (Id a -> Id a) but rather something like (a -> > Id a). Actually, it can make perfect sense: e.g. if the `Id' function acts as a constraint. Stefan ___

Re: [Haskell-cafe] deriving

2008-04-07 Thread Brandon S. Allbery KF8NH
On Apr 7, 2008, at 15:42 , Hans Aberg wrote: But here, one would have to think about how the compiler should be able to distinguish data Bool = False | True instance (Eq) from data Bool = False | True instance Eq Bool where x == y = ... Layout already does that, doesn't it? T

Re: [Haskell-cafe] deriving

2008-04-07 Thread Hans Aberg
On 7 Apr 2008, at 21:15, Dan Weston wrote: To answer your second question (which everyone else ignored): Yes. A different keyword might have been more descriptive, such as "automatically_deriving_instances_for". They are called instantiations, which Haskell can supply automatically in some

Re: [Haskell-cafe] deriving

2008-04-07 Thread Dan Weston
Paul, To answer your second question (which everyone else ignored): Yes. A different keyword might have been more descriptive, such as "automatically_deriving_instances_for". There is always a struggle between concision [1] and descriptiveness in syntax. With short keywords, you pay up front

(forw) Re: [Haskell-cafe] deriving

2008-04-07 Thread John Dorsey
I meant to send this reply to the cafe. - Forwarded message - Date: Mon, 7 Apr 2008 15:05:00 -0400 To: PR Stanley <[EMAIL PROTECTED]> Subject: Re: [Haskell-cafe] deriving Paul, > No, sorry. I'm not sure how this differs from my definition. > Could you elaborate please? Gladly.

Re: [Haskell-cafe] announcing the darcs 2.0.0 release

2008-04-07 Thread David Roundy
On Mon, Apr 07, 2008 at 10:28:12PM +0400, Bulat Ziganshin wrote: > Monday, April 7, 2008, 9:22:25 PM, you wrote: > > * I'm sure there are other new features, but this is all that comes to > >mind at the moment. > > there was some issues with efficiency of darcs 1.x. am i correctly > understoo

Re: [Haskell-cafe] announcing the darcs 2.0.0 release

2008-04-07 Thread Brandon S. Allbery KF8NH
On Apr 7, 2008, at 14:28 , Bulat Ziganshin wrote: Hello David, Monday, April 7, 2008, 9:22:25 PM, you wrote: * I'm sure there are other new features, but this is all that comes to mind at the moment. there was some issues with efficiency of darcs 1.x. am i correctly understood that th

Re: [Haskell-cafe] deriving

2008-04-07 Thread Brandon S. Allbery KF8NH
On Apr 7, 2008, at 12:12 , PR Stanley wrote: Hi data Bool = False | True deriving (Eq, Or, Show, Read) Bool is an instance of Eq, Ord, Show and Read. It is derived form these classes. If that is the meaning of the keyword deriving then wouldn't a different keyword such as from or derivati

Re: [Haskell-cafe] announcing the darcs 2.0.0 release

2008-04-07 Thread Bulat Ziganshin
Hello David, Monday, April 7, 2008, 9:22:25 PM, you wrote: > * I'm sure there are other new features, but this is all that comes to >mind at the moment. there was some issues with efficiency of darcs 1.x. am i correctly understood that these issues was not addressed by new release? its har

Re: [Haskell-cafe] deriving

2008-04-07 Thread PR Stanley
> Hi > data Bool = False | True > deriving (Eq, Or, Show, Read) > > Bool is an instance of Eq, Ord, Show and Read. It is derived form > these classes. No. "deriving ..." here does not mean that Bool is derived from those classes; it's not a statement about inheritance or anything similar. "

[Haskell-cafe] Problem building HXT

2008-04-07 Thread ln
Hi, I would like to try HXT, but I can't manage to build it. I resolved all the dependencies, but I get the following error: > > [EMAIL PROTECTED]:~/Desktop/hxt$ make all > > make -C src all VERSION=7.5 > > make[1]: Entering directory `/home/ln/Desktop/hxt/src' > > make install_local_hxt >

[Haskell-cafe] announcing the darcs 2.0.0 release

2008-04-07 Thread David Roundy
Hello darcs users, I am pleased to announce the release of darcs 2.0.0! It's been a long time coming, and hopefully you will be pleased with the result. Notable new features include (in no particular order): * New ssh-connnection mode that dramatically improves connection times when darcs 2.

Re: [Haskell-cafe] deriving

2008-04-07 Thread John Dorsey
Paul, > Hi > data Bool = False | True > deriving (Eq, Or, Show, Read) > > Bool is an instance of Eq, Ord, Show and Read. It is derived form > these classes. No. "deriving ..." here does not mean that Bool is derived from those classes; it's not a statement about inheritance or anything simil

Re: [Haskell-cafe] deriving

2008-04-07 Thread PR Stanley
Hi data Bool = False | True deriving (Eq, Or, Show, Read) Bool is an instance of Eq, Ord, Show and Read. It is derived form these classes. If that is the meaning of the keyword deriving then wouldn't a different keyword such as from or derivative or even derivation be closer to the semantics

Re: [Haskell-cafe] Re: type families and type signatures

2008-04-07 Thread Tom Schrijvers
On Mon, 7 Apr 2008, Mark P Jones wrote: The surprising thing about this example is the fact that the definition of foo is accepted, and not the fact that the definition of foo' is rejected. At least in Manuel's "equivalent" program using functional dependencies, both functions have ambiguous ty

Re: [Haskell-cafe] Parsec expressions with alphaNum operators

2008-04-07 Thread Chris Casinghino
Hi, 2008/4/7 Paul Keir <[EMAIL PROTECTED]>: > I'm using buildExpressionParser, and I'd like to use alphanumeric operator > characters. I get an (unexpected "a") error though. With a test string like > "-a" if "a" is used in any of the "reservedOpNames". I'm aiming for the > Fortran operators like

Re: [Haskell-cafe] deriving

2008-04-07 Thread Conal Elliott
I'm not getting it. Are you thinking that Bool itself "is derived form these classes", rather than those four instances for Bool? - Conal On Mon, Apr 7, 2008 at 9:12 AM, PR Stanley <[EMAIL PROTECTED]> wrote: > Hi > data Bool = False | True > deriving (Eq, Or, Show, Read) > > Bool is an instanc

[Haskell-cafe] deriving

2008-04-07 Thread PR Stanley
Hi data Bool = False | True deriving (Eq, Or, Show, Read) Bool is an instance of Eq, Ord, Show and Read. It is derived form these classes. If that is the meaning of the keyword deriving then wouldn't a different keyword such as from or derivative or even derivation be closer to the semantics

[Haskell-cafe] Parsec expressions with alphaNum operators

2008-04-07 Thread Paul Keir
Hi, I'm using buildExpressionParser, and I'd like to use alphanumeric operator characters. I get an (unexpected "a") error though. With a test string like "-a" if "a" is used in any of the "reservedOpNames". I'm aiming for the Fortran operators like ".and.". The listing below may be helpful

Re: [Haskell-cafe] ANNOUNCE: Well-Typed LLP - The Haskell Consultants

2008-04-07 Thread Seth Gordon
Ian Lynagh wrote: Fellow Haskellers, We (Björn Bringert, Duncan Coutts and Ian Lynagh) are pleased to announce that we have recently set up a Haskell consultancy company, Well-Typed LLP (http://www.well-typed.com/). Congratulations! Do you have a plan to market your services to people who mig

Re: [Haskell-cafe] [GSoC] WWW::Mechanize-like package for Haskell

2008-04-07 Thread Max Desyatov
On Mon, Apr 7, 2008 at 4:11 PM, Thomas Schilling <[EMAIL PROTECTED]> wrote: > It doesn't have to be perfect. Make sure you know how to use monad > transformers. Also take a look at tag soup and the various HTML/XML > parsers. I'm sure there's plenty to work on. > > My guess would be, tha

RE: [Haskell-cafe] Parsec Expected Type

2008-04-07 Thread Paul Keir
Thanks. reservedOp is a better fit; ":+" should only be ":+". I also overcame my type issues in an ad-hoc manner, adding >> return () whenever I needed to. -Original Message- From: Tillmann Rendel [mailto:[EMAIL PROTECTED] Sent: 30 March 2008 12:30 To: Paul Keir; haskell-cafe@haskell.o

Re: [Haskell-cafe] Re: Shouldn't this loop indefinitely => take (last [0..]) [0..]

2008-04-07 Thread David Roundy
On Mon, Apr 07, 2008 at 04:52:51AM -0700, John Meacham wrote: > On Mon, Apr 07, 2008 at 04:45:31AM -0700, David Roundy wrote: > > I wonder about the efficiency of this implementation. It seems that for > > most uses the result is that the size of a Nat n is O(n), which means that > > in practice y

Re: [Haskell-cafe] Re: Shouldn't this loop indefinitely => take (last [0..]) [0..]

2008-04-07 Thread Joachim Breitner
Hi, Am Freitag, den 04.04.2008, 22:44 +0100 schrieb Neil Mitchell: > Hi > > > We can however write function like this: > > > > eqLengths [] [] = True > > eqLengths (x:xs) (y:ys) = eqLengths ys xs > > eqLengths _ _ = False > > > > which looks just fine for me. > > I have this defined functio

Re: [Haskell-cafe] Re: type families and type signatures

2008-04-07 Thread Mark P Jones
The surprising thing about this example is the fact that the definition of foo is accepted, and not the fact that the definition of foo' is rejected. At least in Manuel's "equivalent" program using functional dependencies, both functions have ambiguous types, and hence both would be rejected. It

Re: [Haskell-cafe] [GSoC] WWW::Mechanize-like package for Haskell

2008-04-07 Thread Thomas Schilling
On 7 apr 2008, at 15.36, Yitzchak Gale wrote: Max Desyatov wrote: I'm interested in working on a library for a stateful web browsing in Haskell during Google Summer of Code. Thomas Schilling wrote: Also, for a GSoC proposal you should try to convince the mentors, why your project is use

Re: [Haskell-cafe] Memory allocation in extractor function (newbie question)

2008-04-07 Thread Alexander Kireyev
On Mon, Apr 7, 2008 at 4:16 PM, Yitzchak Gale <[EMAIL PROTECTED]> wrote: > You didn't show us the code for countForPoints. I'll bet you wrote > something like > > countForPoints area ls count points = > sum $ map (countPathsFrom area (count + 1) ls) points > > Unfortunately, the standard sum

Re: [Haskell-cafe] [GSoC] WWW::Mechanize-like package for Haskell

2008-04-07 Thread Yitzchak Gale
Max Desyatov wrote: >> I'm interested in working on a library for a stateful web browsing in >> Haskell during Google Summer of Code. Thomas Schilling wrote: > Also, for a GSoC proposal you should try to convince the mentors, why your > project is useful for Haskell in general. So maybe you have

Re: [Haskell-cafe] The range operator

2008-04-07 Thread Roel van Dijk
class Enum a where ... -- | Used in Haskell's translation of [n,n'..m]. enumFromThenTo :: a -> a -> a -> [a] So [x, y .. z] becomes "enumFromThenTo x y z". Each instance of Enum is free to implement enumFromThenTo and friends in any way it likes. So with Ints you have [1, 3 .. 10] :: [Int]

Re: [Haskell-cafe] Memory allocation in extractor function (newbie question)

2008-04-07 Thread Yitzchak Gale
Alexander Kireyev wrote: > While trying to write a program for the countPaths Code Jam problem I > ran into what seems to me as a weird behaviour in terms of memory > allocation... > The profiling log (./paths +RTS -P) shows the following time/space > behaviour for them... Hi Alexander, I'm

Re: [Haskell-cafe] [GSoC] WWW::Mechanize-like package for Haskell

2008-04-07 Thread Thomas Schilling
On 7 apr 2008, at 14.46, Max Desyatov wrote: Hi, I'm interested in working on a library for a stateful web browsing in Haskell during Google Summer of Code. The basic idea is described at http://hackage.haskell.org/trac/summer-of-code/ticket/1107. WWW::Mechanize is a ready to use library wri

[Haskell-cafe] [GSoC] WWW::Mechanize-like package for Haskell

2008-04-07 Thread Max Desyatov
Hi, I'm interested in working on a library for a stateful web browsing in Haskell during Google Summer of Code. The basic idea is described at http://hackage.haskell.org/trac/summer-of-code/ticket/1107. WWW::Mechanize is a ready to use library written in Perl, though I used python's mechanize wh

Re: [Haskell-cafe] ANN: Hayoo! beta 0.1

2008-04-07 Thread Uwe Schmidt
Uwe Schmidt wrote: > Lieber Herr Hübel, > lieber Herr Schlatt, sorry for spamming haskell-cafe Uwe ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Re: Shouldn't this loop indefinitely => take (last [0..]) [0..]

2008-04-07 Thread Aaron Denney
On 2008-04-04, Neil Mitchell <[EMAIL PROTECTED]> wrote: >> What do you mean by "proper Lazy naturals"? Peano ones? > > Yes Not _strictly_ necessary. And I'd definitely like some suitable typeclass put in place. This represents positive arithmetic with a list homomorphism that forgets the elemen

Re: [Haskell-cafe] ANN: Hayoo! beta 0.1

2008-04-07 Thread Philip Müller
On Sun, 06 Apr 2008 14:07:22 +0200, wrote: > Hello, > > we are pleased to announce the first beta release of Hayoo!, a Haskell > API > search engine providing advanced features like suggestions, > find-as-you-type, > fuzzy queries and much more. > > Visit Hayoo! here: http://holumbus.fh-wedel.de

Re: [Haskell-cafe] The range operator

2008-04-07 Thread PR Stanley
At 12:28 07/04/2008, you wrote: On Fri, Apr 4, 2008 at 10:49 PM, Andrew Coppin <[EMAIL PROTECTED]> wrote: > More to the point, the range y..z goes in steps of y-z. ;-) [x,y..z] goes in steps of y-x ;-), [y..z] goes in steps of 1 (depending on the type). Could you elaborate please?

Re: [Haskell-cafe] Re: Shouldn't this loop indefinitely => take (last [0..]) [0..]

2008-04-07 Thread John Meacham
On Mon, Apr 07, 2008 at 04:45:31AM -0700, David Roundy wrote: > I wonder about the efficiency of this implementation. It seems that for > most uses the result is that the size of a Nat n is O(n), which means that > in practice you probably can't use it for large numbers. > > e.g. it seems like >

Re: [Haskell-cafe] ANN: Hayoo! beta 0.1

2008-04-07 Thread Uwe Schmidt
Lieber Herr Hübel, lieber Herr Schlatt, ich habe gerade das Announcement von Holumbus in haskell.org gelesen und natürlich auch Holumbus ausprobiert. RICHTIG GUT! Viele Gruesse Uwe Schmidt ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http:

Re: [Haskell-cafe] Re: Shouldn't this loop indefinitely => take (last [0..]) [0..]

2008-04-07 Thread David Roundy
On Sun, Apr 06, 2008 at 07:12:24AM -0700, John Meacham wrote: > On Fri, Apr 04, 2008 at 04:46:22PM +0100, Neil Mitchell wrote: > > Where length xs = 1 and ys = 1000. This takes 1000 steps to tell the > > Int's aren't equal, since we don't have proper lazy naturals. If we > > did, it would take 2 st

[Haskell-cafe] Re: Function Precedence

2008-04-07 Thread Aaron Denney
On 2008-04-03, Chris Smith <[EMAIL PROTECTED]> wrote: > Hans Aberg wrote: >> This problem is not caused by defining f+g, but by defining numerals as >> constants. > > Yup. So the current (Num thing) is basically: > > 1. The type thing is a ring > 2. ... with signs and absolute values > 3. ... alon

Re: [Haskell-cafe] The range operator

2008-04-07 Thread Roel van Dijk
On Fri, Apr 4, 2008 at 10:49 PM, Andrew Coppin <[EMAIL PROTECTED]> wrote: > More to the point, the range y..z goes in steps of y-z. ;-) [x,y..z] goes in steps of y-x ;-), [y..z] goes in steps of 1 (depending on the type). ___ Haskell-Cafe mailing list Ha

[Haskell-cafe] Memory allocation in extractor function (newbie question)

2008-04-07 Thread Alexander Kireyev
Hello, While trying to write a program for the countPaths Code Jam problem I ran into what seems to me as a weird behaviour in terms of memory allocation. The task is to count the number of way you can spell a certain "word" by walking some path on a board of letters. Being a newbie I started wi

Re: [Haskell-cafe] Re: type families and type signatures

2008-04-07 Thread Tom Schrijvers
type instance Id Int = Int foo :: Id a -> Id a foo = id foo' :: Id a -> Id a foo' = foo Is this expected? Yes, unfortunately, this is expected, although it is very unintuitive. This is for the following reason. Huh? This sounds very wrong to me, simply because foo and foo' have the ve

[Haskell-cafe] Re: type families and type signatures

2008-04-07 Thread apfelmus
Manuel M T Chakravarty wrote: Ganesh Sittampalam: The following program doesn't compile in latest GHC HEAD, although it does if I remove the signature on foo'. {-# LANGUAGE TypeFamilies #-} module Test7 where type family Id a type instance Id Int = Int foo :: Id a -> Id a foo = id foo' ::