Re: Closed Type Families: type checking dumbness? [was: separate instance groups]

2015-06-07 Thread adam vogt
Hi, AntC's f can be done without -XOverlappingInstances http://lpaste.net/7559485273839501312, using the trick didn't work in #9918. I'm not sure extra syntax is justified to clean up this rare case. Regards, Adam On Sun, Jun 7, 2015 at 11:12 AM, Dan Doel dan.d...@gmail.com wrote: It

Re: HEADS UP: Final call for 7.10.2 is soon

2015-06-02 Thread adam vogt
On Jun 2, 2015 6:03 PM, Wolfgang Jeltsch g9ks1...@acme.softbase.org wrote: Hi, bug #10009 appears on the status page with status “new”, although the bug should have been fixed in HEAD. Can this fix *please* be a part of GHC 7.10.2? At the moment, this bug breaks the incremental-computing

Re: Ambiguity check and type families

2015-06-02 Thread adam vogt
Hi Wolfgang, https://ghc.haskell.org/trac/ghc/ticket/10009 might be the same regression (fixed in HEAD) Regards, Adam On Tue, Jun 2, 2015 at 12:28 PM, Wolfgang Jeltsch g9ks1...@acme.softbase.org wrote: Hi, the following (contrived) code is accepted by GHC 7.8.3, but not 7.10.1: {-#

Re: overlapping instances 7.10.1

2015-05-21 Thread adam vogt
Hi Sergei, I think you should use {-# OVERLAPPABLE #-}: see the description here https://ghc.haskell.org/trac/ghc/ticket/9242#comment:16 which is probably in the manual somewhere too. Regards, Adam On Thu, May 21, 2015 at 9:40 AM, Sergei Meshveliani mech...@botik.ru wrote: People, I wrote

Re: Record Puns/Wildcards

2015-02-24 Thread adam vogt
Hi Ben, With ghc-7.8.4 I get a different error Empty record update of: default_config when using a wildcard to update a record. I think you can't use wildcards in record updates because it's harder (for users and for ghc) to figure out which fields are involved when you don't name a constructor.

type checker plugin success depends on whether an expression is manually inlined

2015-02-19 Thread adam vogt
Hello list, The following file compiles with my plugin. It makes a data family HList have role representational in a way that I believe is safe: https://github.com/aavogt/HListPlugin/blob/master/ex/Coerce.hs#L19 I expect the highlighted line to be acceptable. However, it seems that the plugin

Re: ApplicativeDo

2015-02-18 Thread adam vogt
What part of applicative-quoters is broken for you? 0.1.0.8 compiles on ghc-7.8.4 here, and [ado| a - Just (); b - Just 2; (a,b) |] evaluates to Just ((),2) as it should. ___ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org

Re: type checker plugin does not affect inferred type signatures

2015-02-16 Thread adam vogt
Hi Adam, I've added a README which tries to explain things: https://github.com/aavogt/HListPlugin When I produce a wanted constraint from a wanted constraint, things work as I wanted. Thanks for the suggestion! Regards, Adam On Mon, Feb 16, 2015 at 4:36 AM, Adam Gundry a...@well-typed.com

type checker plugin does not affect inferred type signatures

2015-02-14 Thread adam vogt
Hello, Using ghc-7.10 rc1, I am trying to write a type checker plugin that adds wanted constraint which helps ghc to infer more types. However, it seems that the wanted constraints I add don't get added to the inferred type of the declaration, so that I get a type error like: a.hs:1:1: Warning:

Re: [Haskell-cafe] Injective type families for GHC

2015-02-10 Thread adam vogt
On Tue, Feb 10, 2015 at 6:38 AM, Jan Stolarek jan.stola...@p.lodz.pl wrote: I don't know how realistic this is but a constraint (HLength x ~ HLength y) would ideally have the same result as SameLength x y. I'm not sure if I understand that part. HLength is not injective. How would injectivity

Re: [Haskell-cafe] Injective type families for GHC

2015-02-09 Thread adam vogt
Hi Jan, One example is https://github.com/haskell/vector/issues/34 I see lots of potential uses in HList. For example in HZip.hs there's a Zip using type families: type family HZipR (x::[*]) (y::[*]) :: [*] type instance HZipR '[] '[] = '[] type instance HZipR (x ': xs) (y ': ys) = (x,y) ':

Re: Restricted Template Haskell

2015-01-30 Thread adam vogt
Hi Greg, Perhaps a less-invasive way to implement the -XSafe part of your proposal would be to provide a module like: module Language.Haskell.TH.Safe ( module Language.Haskell.TH, reifyWithoutNameG, ) where import Language.Haskell.TH hiding (runIO, reify*) where reifyWithoutNameG is the

Re: ghc-7.10.0 type inference regression when faking injective type families

2015-01-20 Thread adam vogt
I've added it as https://ghc.haskell.org/trac/ghc/ticket/10009 On Tue, Jan 20, 2015 at 11:23 AM, Richard Eisenberg e...@cis.upenn.edu wrote: After quite a bit of thought, I agree that this is a regression and that the original program should be accepted. Make a bug report! Thanks, Richard

ghc-7.10.0 type inference regression when faking injective type families

2015-01-19 Thread adam vogt
Hello List, With ghc - 7.8 and 7.6 the following program is accepted: {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeFamilies #-} class (UnF (F a) ~ a, Show a) = C a where type F a f :: F a - a type family UnF a g :: forall a. C a = a - String g _ = show a where a = f

Re: Old code broken by new Typeable class

2014-08-05 Thread adam vogt
Hi Volker, You can use this extension: http://www.haskell.org/ghc/docs/latest/html/users_guide/deriving.html#stand-alone-deriving to write that orphan Typeable instance for most ghcs (probably 6.10 is the earliest). It might be worth pushing for a Typeable instance to be added to the unix

Re: GHCJS now runs Template Haskell on node.js - Any interest in out of process TH for general cross compilation?

2014-07-05 Thread adam vogt
Zeroth takes the first approach. It only supports a subset of TH (DecsQ splices) however. http://hackage.haskell.org/package/zeroth https://github.com/aavogt/zeroth is a fork that works with more recent haskell-src-exts and ghc On Sat, Jul 5, 2014 at 3:59 PM, John Meacham j...@repetae.net

Data.Type.Equality.== works better when used at kind * - * - Bool

2014-05-30 Thread adam vogt
Hello List, Given the following definitions: class HEq (x :: k) (y :: k) (b :: Bool) | x y - b instance ((Proxy x == Proxy y) ~ b) = HEq x y b -- (A) instance ((x == y) ~ b) = HEq x y b -- (B) The instance (A) lets HList compile, which can be reproduced with: darcs get

Re: Tightening up on inferred type signatures

2014-04-21 Thread adam vogt
] GHC generally obeys this rule ] ] · If GHC infers a type f::type, then it’s OK for you to add a type ] signature saying exactly that. That rule suggests that -XScopedTypeVariables should be on by default, and that you shouldn't need a forall to bring the type variables into scope. I

Re: importing (=) from GHC.TypeLits

2014-03-15 Thread adam vogt
http://www.haskell.org/ghc/docs/7.8.1-rc2/html/users_guide/syntax-extns.html#explicit-namespaces is the trick On Sat, Mar 15, 2014 at 12:47 PM, Henning Thielemann lemm...@henning-thielemann.de wrote: I want to import Nat and type-level (=) from GHC.TypeLits: import GHC.TypeLits (Nat, (=))

Re: splicing varPs in quasi-quote brackets

2014-03-14 Thread adam vogt
Hello Christian, It seems new to me that $( ) is allowed in patterns. I would have used lamE in something like: [| $(varE v) = return . SM.concatMapM $(lamE [varP v] (buildRns f (xs++[w]) ys))) |] Regards, Adam ___ Glasgow-haskell-users mailing list

Re: Feature request: Vacuous/error constraint (related to 7.7 closed type families regression)

2014-01-14 Thread adam vogt
Hi Merijn, Let me suggest the Fail type family in http://www.haskell.org/pipermail/haskell-cafe/2013-November/111549.html -- Adam On Tue, Jan 14, 2014 at 8:56 AM, Merijn Verstraaten mer...@inconsistent.nl wrote: I was trying to fix one of my closed type families examples for the new syntax,

Why cannot inferred type signatures restrict (potentially) ambiguous type variables?

2013-10-12 Thread adam vogt
Hello, I have code: {-# LANGUAGE FlexibleInstances, MultiParamTypeClasses, ScopedTypeVariables, TypeFamilies #-} class C a b where c :: a - b instance (int ~ Integer) = C Integer int where c = (+1) c2 :: forall a b c. (C a b, C b c) = a - c c2 x = c (c x :: b) c2 x = c ((c :: a - b) x) Why