On 05/04/15 15:54, Daniel Trstenjak wrote:
>
> On Sun, Apr 05, 2015 at 03:25:01PM +0300, Roman Cheplyaka wrote:
>> Data.ByteString.Lazy.Char8 exports the same lazy bytestring type as
>> Data.ByteString.Lazy. Only functions and instances differ.
>
> So my only option in this case is to define a ne
On Sun, Apr 05, 2015 at 03:25:01PM +0300, Roman Cheplyaka wrote:
> Data.ByteString.Lazy.Char8 exports the same lazy bytestring type as
> Data.ByteString.Lazy. Only functions and instances differ.
So my only option in this case is to define a newtype wrapper
for Data.ByteString.Lazy and then defin
the same lazy bytestring type as
>> Data.ByteString.Lazy. Only functions and instances differ.
>
> Well, *instances* can't differ...
>
>>
>> On 05/04/15 15:19, Daniel Trstenjak wrote:
>>>
>>> Hi,
>>>
>>> I'm getting th
Data.ByteString.Lazy.Char8 exports the same lazy bytestring type as
Data.ByteString.Lazy. Only functions and instances differ.
On 05/04/15 15:19, Daniel Trstenjak wrote:
>
> Hi,
>
> I'm getting the compile error:
>
> Gamgine/Image/PNG/Internal/Parser.hs:14:10:
>
Hi,
I'm getting the compile error:
Gamgine/Image/PNG/Internal/Parser.hs:14:10:
Functional dependencies conflict between instance declarations:
instance Monad m => Stream LB.ByteString m Word8
-- Defined at Gamgine/Image/PNG/Internal/Parser.hs:14:10
instance
rn kinds too?...
Yes, I ran into this a while ago. A function dependency on a kind seems to work
remarkably well.
Can we have type families that return kinds? No. Well, not yet. Functional
dependencies inform type inference but don't produce any evidence in Core -- a
dependency is o
Hello,
Maybe this is well known already (or maybe it's a bug), but lately I've
again found that functional
dependencies are more versatile than type families. In particular, they can
be used to compute
kinds from types, whereas type families cannot. Consider the code below,
which im
Reid,
Ah yes. The interaction of functional dependencies and GADTs is flaky and
unpredictable in both 6.8 and 6.10. It's actually rather tricky to get right
-- see our ICFP'08 paper.
You may have better luck using type families instead of functional
dependencies, but even then
tmp/fundep.hs:10:0:
Couldn't match expected type `fb' against inferred type `fa'
`fb' is a rigid type variable bound by
the type signature for `baz' at /tmp/fundep.hs:9:21
`fa' is a rigid type variable bound by
the type signat
| while both GHC and Hugs accept this variation:
|
| class FD a b | a -> b
| f :: (FD t1 t2, FD t1 t3) => t1 -> t2 -> t3
| f x y = undefined
|
| and infer the type of 'f' to be 'f :: (FD t1 t3) => t1 -> t3 -> t3'.
|
| So they use the FD globally (when checking use of 'f'), but not local
By "global" I really meant "throughout the scope of the type variable concerned.
Nevertheless, the program you give is rejected, even though the scope is global:
class FD a b | a -> b
f :: (FD t1 t2, FD t1 t3) => t1 -> t2 -> t3
f x y = y
Both GHC and Hugs erroneously reject the program,
w
o:[EMAIL PROTECTED]
| Sent: 24 September 2008 19:27
| To: Simon Peyton-Jones; glasgow-haskell-users@haskell.org
| Subject: Re: GADTs and functional dependencies
|
| >> This has never worked with fundeps, because it involves a *local* type
| equality (one that holds
| >> in some places
This has never worked with fundeps, because it involves a *local* type equality (one that holds
in some places and not others) and my implementation of fundeps is fundamentally based on
*global* equality. Prior to GADTs that was fine!
Actually, how does that relate to reasoning under assumptio
Hello Simon,
thank you for your extensive answer!
I think, I’ll try to work around the fundep deficiencies and if that doesn’t
work, switch to type families.
But your answer raised further questions/comments:
> class (F a ~ b) => C a b
> type family F a
>
> (Note for 6.10 use
This has never worked with fundeps, because it involves a *local* type equality (one that holds in
some places and not others) and my implementation of fundeps is fundamentally based on *global*
equality. Prior to GADTs that was fine!
Thanks for the explanation, Simon - it clears up some outst
Wolfgang writes
| > data GADT a where
| >
| > GADT :: GADT ()
| >
| > class Class a b | a -> b
| >
| > instance Class () ()
| >
| > fun :: (Class a b) => GADT a -> b
| > fun GADT = ()
You're right that this program should typecheck. In the case branch we
discover (locally) that a~(), and he
Am Mittwoch, 24. September 2008 15:11 schrieb Ian Lynagh:
> On Wed, Sep 24, 2008 at 12:55:29PM +0200, Wolfgang Jeltsch wrote:
> > I thought, someone said that with the new typing machinery in GHC 6.10,
> > more functional dependency programs are accepted because functional
>
On Wed, Sep 24, 2008 at 12:55:29PM +0200, Wolfgang Jeltsch wrote:
>
> I thought, someone said that with the new typing machinery in GHC 6.10, more
> functional dependency programs are accepted because functional dependencies
> are handled similarly to type families (or something lik
gt;
> type family F a
> type instance F () = ()
>
> fun :: GADT a -> F a
> fun GADT = ()
Exactly. But this makes my code incompatible with GHC 6.6. :-(
I thought, someone said that with the new typing machinery in GHC 6.10, more
functional dependency programs are accepted becau
On Tue, Sep 23, 2008 at 1:44 PM, Chris Kuklewicz
<[EMAIL PROTECTED]> wrote:
> You cannot create a normal function "fun". You can make a type class
> function
>
> fun :: Class a b => GADT a -> b
>
>> data GADT a where
>> GADT :: GADT ()
>> GADT2 :: GADT String
>>
>> -- fun1 :: GADT () -> ()
You cannot create a normal function "fun". You can make a type class function
fun :: Class a b => GADT a -> b
data GADT a where
GADT :: GADT ()
GADT2 :: GADT String
-- fun1 :: GADT () -> () -- infers type
fun1 g = case g of
(GADT :: GADT ()) -> ()
-- fun2 :: GADT String
On Tue, Sep 23, 2008 at 9:07 AM, Wolfgang Jeltsch
<[EMAIL PROTECTED]> wrote:
> Hello,
>
> please consider the following code:
>
>> {-# LANGUAGE GADTs, MultiParamTypeClasses, FunctionalDependencies #-}
>>
>> data GADT a where
>>
>> GADT :: GADT ()
>>
>> class Class a b | a -> b
>>
>> instance Cl
On Tue, Sep 23, 2008 at 9:36 AM, Wolfgang Jeltsch
<[EMAIL PROTECTED]> wrote:
> Am Dienstag, 23. September 2008 18:19 schrieben Sie:
>> On Tue, Sep 23, 2008 at 6:07 PM, Wolfgang Jeltsch
>>
>> <[EMAIL PROTECTED]> wrote:
>> > Hello,
>> >
>> > please consider the following code:
>> >> {-# LANGUAGE GADT
On Tue, Sep 23, 2008 at 9:36 AM, Wolfgang Jeltsch
<[EMAIL PROTECTED]> wrote:
> Am Dienstag, 23. September 2008 18:19 schrieben Sie:
>> On Tue, Sep 23, 2008 at 6:07 PM, Wolfgang Jeltsch
>>
>> <[EMAIL PROTECTED]> wrote:
>> > Hello,
>> >
>> > please consider the following code:
>> >> {-# LANGUAGE GADT
On Tue, Sep 23, 2008 at 6:36 PM, Wolfgang Jeltsch
<[EMAIL PROTECTED]> wrote:
> Pattern matching against the data constructor GADT specializes a to (). Since
> Class uses a functional dependency, it is clear that b has to be ().
True, but it wont work if you provide () as the result and b in the
e
Am Dienstag, 23. September 2008 18:19 schrieben Sie:
> On Tue, Sep 23, 2008 at 6:07 PM, Wolfgang Jeltsch
>
> <[EMAIL PROTECTED]> wrote:
> > Hello,
> >
> > please consider the following code:
> >> {-# LANGUAGE GADTs, MultiParamTypeClasses, FunctionalDependencies #-}
> >>
> >> data GADT a where
> >>
On Tue, Sep 23, 2008 at 6:07 PM, Wolfgang Jeltsch
<[EMAIL PROTECTED]> wrote:
> Hello,
>
> please consider the following code:
>
>> {-# LANGUAGE GADTs, MultiParamTypeClasses, FunctionalDependencies #-}
>>
>> data GADT a where
>>
>> GADT :: GADT ()
>>
>> class Class a b | a -> b
>>
>> instance Cl
Hello,
please consider the following code:
> {-# LANGUAGE GADTs, MultiParamTypeClasses, FunctionalDependencies #-}
>
> data GADT a where
>
> GADT :: GADT ()
>
> class Class a b | a -> b
>
> instance Class () ()
>
> fun :: (Class a b) => GADT a -> b
> fun GADT = ()
I’d expect this to wor
Hi, Chris
Thanks for your answer. I guess that my intuitions of what functional
dependencies and context meant were not very accurate (see below)
class C m f n | m -> n, f -> n where
c :: m -> f -> Bool
The "m->n" functional dependency means that I tell you
By the way, if you make the class C fundep declaration into:
> class C m f n | m f -> n where
then it compiles. This means ((M n) and (F n) imply N) and ("any m" and F'
imply N') which no longer conflict.
Daniel Gorín wrote:
> Hi
>
> I have some code that uses MPTC + FDs + flexible and undeci
By the "m->n" functional dependency, the above implies that _any_ "m" must map
to the type M2.N: "m -> M2.N"
This kills you in M3...
>
>> module M3
>>
>> where
>>
>> import M1
>> import M2()
>>
>> data N
27;= F' (F N)
>
> data N = N
>
> instance C m (F N) N => C m F' N where
> c m (F' f) = c m f
> module M3
>
> where
>
> import M1
> import M2()
>
> data N' = N'
>
> go :: M N' -> F N' -> Bool
> go m f =
Am Mittwoch, 17. August 2005 10:52 schrieb Simon Peyton-Jones:
> >From the instance declaration
>
> instance Fib Zero (Succ Zero)
> we get the improvement rule
> Fib Zero a ==> a=(Succ Zero)
> We get a similar rule from
> instance Fib (Succ Zero) (Succ Zero)
> But the instance dec
Am Dienstag, 16. August 2005 21:17 schrieb Keean Schupke:
> Attached are 3 Haskell modules used for type level programming. These
Thank you!
> The general 'trick' if you will is to imlement each funtion as a type
> class, pattern matching the
> types to instances in a type-level analogue of the v
Am Dienstag, 16. August 2005 19:45 schrieb Iavor Diatchki:
> Hello,
> I am not sure what GHC is doing, it certainly seems to be
> inconsistent. In Hugs both the examples work. In case you are
> interested, here is how you can get a version that works in
> both Hugs and GHC (I just modified your c
instantiates its type, and then tries to solve the constraint (Fib (Succ
(Succ...)) n). Now it must use the instance declarations to simplify
it, and in doing so that exposes more constraints that do force n to be
the type you get.
I agree this is desperately confusing, and I'm not say
Attached are 3 Haskell modules used for type level programming. These
were developed as background work for the HList paper, but are not in
the final libraries as they are 'off topic' as it were. They were
however useful in testing type-level programming concepts.
Control.hs - This contains ty
Hello,
I am not sure what GHC is doing, it certainly seems to be
inconsistent. In Hugs both the examples work. In case you are
interested, here is how you can get a version that works in
both Hugs and GHC (I just modified your code a little):
{-# OPTIONS -fglasgow-exts -fallow-undecidable-instan
Hello Keean!
Am Dienstag, 16. August 2005 13:48 schrieb Keean Schupke:
> Picked up on this late... I have working examples of add etc under
> ghc/ghci...
> I can't remeber all the issues involved in getting it working, but I can
> post the
> code for add if its any use?
Yes, that would be nice. I
Succ (Succ (Succ Zero)))
Best regards,
Dirk
Simon
| -Original Message-
| From: [EMAIL PROTECTED]
[mailto:glasgow-haskell-users-
| [EMAIL PROTECTED] On Behalf Of Dirk Reckmann
| Sent: 21 July 2005 10:30
| To: glasgow-haskell-users@haskell.org
| Subject: Functional Dependencies
|
|
PROTECTED] On Behalf Of Dirk Reckmann
> | Sent: 21 July 2005 10:30
> | To: glasgow-haskell-users@haskell.org
> | Subject: Functional Dependencies
> |
> | Hello everybody!
> |
> | I wanted to have some fun with functional dependencies (see
> | http://www.cs.chalmers.se/~hallgr
Bool, so it's a bit misleading to universally quantify it.
Simon
| -Original Message-
| From: [EMAIL PROTECTED]
[mailto:glasgow-haskell-users-
| [EMAIL PROTECTED] On Behalf Of Dirk Reckmann
| Sent: 21 July 2005 10:30
| To: glasgow-haskell-users@haskell.org
| Subject: Functional
Hello everybody!
I wanted to have some fun with functional dependencies (see
http://www.cs.chalmers.se/~hallgren/Papers/wm01.html), and tried some
examples from this paper as well as some own experiments. The idea is to use
the type checker for computations by "abuse" of type cl
Manuel M T Chakravarty wrote:
I accept that this is the process by which GHC computes these types, but
it does violate the principal types property, doesn't it? The relation
Int -> () <= forall c. Int -> c
does not hold.
I realise that principal types and principal typings are slightly
di
those underlying GHC's type system.
> | Again, in GHCi,
> |
> | > *FDs> let bar x = foo ((x::Int, x), (x, x))
> | > *FDs> :t bar
> | > bar :: Int -> ()
> |
> | (which by itself is bizarre)
>
> This is the first time when the functional dependency
Manuel
Your short program tickles a lot of different questions. Here's an
explanation.
Simon
| Assume the following type class declarations with functional
| dependencies:
Actually much of the behaviour you see happens without fundeps.
| > {-# OPTIONS -fglasgow-exts #-}
| >
| &g
Iavor Diatchki wrote:
> Hi,
>
> On Apr 3, 2005 7:33 AM, Manuel M T Chakravarty <[EMAIL PROTECTED]> wrote:
> > Assume the following type class declarations with functional
> > dependencies:
> >
> > > {-# OPTIONS -fglasgow-exts #-}
> > >
>
Hi,
On Apr 3, 2005 7:33 AM, Manuel M T Chakravarty <[EMAIL PROTECTED]> wrote:
> Assume the following type class declarations with functional
> dependencies:
>
> > {-# OPTIONS -fglasgow-exts #-}
> >
> > class C a b c | a b -> c where
> > foo :: (a, b)
Assume the following type class declarations with functional
dependencies:
> {-# OPTIONS -fglasgow-exts #-}
>
> class C a b c | a b -> c where
> foo :: (a, b) -> c
>
> instance C a a r => C a (b, c) r where
> foo (a, (b, c)) = foo (a, a)
Now, in GHCi (version
5.04, but
I'm not going to be totally thorough!
Please yell if any similar mysterious things happen. I appreciate
the report.
Simon
| -Original Message-
| From: Christian Maeder [mailto:[EMAIL PROTECTED]]
| Sent: 28 June 2002 18:09
| To: [EMAIL PROTECTED]
| Subject: function
Simon Peyton-Jones wrote:
> Jeff Lewis has heroically put in the code for 95% of functional
> dependencies,
> but I don't think he's quite finished.
>
> Jeff, what's your plan?
>
I'd like to have some time to finish this up in the next month - hopefully
Jeff Lewis has heroically put in the code for 95% of functional
dependencies,
but I don't think he's quite finished.
Jeff, what's your plan?
Simon
| -Original Message-
| From: Michael Marte [mailto:[EMAIL PROTECTED]]
| Sent: 04 April 2000 09:03
| To: [EMAIL PROTECTED
Hello,
I have been using multi-parameter type classes with functional
dependencies (as implemented in Hugs) for a while now and I am quite happy
with it. For performance reasons, I want to compile my stuff with ghc, but
unfortunately the type inference engine of ghc 4.07 does not yet take
It seems that functional dependencies in GHC-4.06 are finished enough
to use them in lang/monads modules. I suggest adding "| m -> s"
to MonadReader, MonadWriter and MonadState class definitions. Works
for me.
54 matches
Mail list logo