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  wrote:

> It seems to me the problem is that there's no way to define classes by
> consecutive cases to match the family definitions. I don't know what a good
> syntax for that would be, since 'where' syntax is taken for those. But it
> seems like it would correspond fill the hole here.
>
> On Sun, Jun 7, 2015 at 7:27 AM, Richard Eisenberg 
> wrote:
>
>> This is all expected behavior. GHC's lazy overlap checking for class
>> instances simply cannot apply to type families -- it would be unsound. I'm
>> afraid I don't see what can be improved here.
>>
>> Richard
>>
>> On Jun 6, 2015, at 2:04 AM, AntC  wrote:
>>
>> >> From: AntC
>> >> Date: 2015-06-04 22:39:25 GMT
>> >>
>> >> Take the standard example for partial overlaps.
>> >> Suppose I have a class: ...
>> >
>> >> I'm also getting (in more complex examples)
>> >> GHC complaining it can't infer the types
>> >> for the result of f.
>> >> So now I'm having to put type equality
>> >> constraints on the class instances,
>> >> to assure it that F comes up with
>> >> the right type.
>> >
>> > In a reduced example, I'm still getting
>> > poor type checking. This is GHC 7.8.3.
>> > This seems so dumb, I'm suspecting a defect,
>> > It's similar to
>> > but much more glaring than:
>> > https://ghc.haskell.org/trac/ghc/ticket/10227
>> > https://ghc.haskell.org/trac/ghc/ticket/9918
>> >
>> > {-# LANGUAGE TypeFamilies,
>> > FlexibleInstances
>> >   #-}
>> > module ClosedTypeFamily where
>> >
>> >data Foo b c = Foo b c deriving (Eq, Read, Show)
>> >
>> >type family F awhere
>> >  F (Foo Int c)  = Int-- Foo Int is first instance
>> >  F (Foo b Char) = Char
>> >
>> >class C a where f :: a -> F a
>> >
>> >instance C (Foo Int c) where  -- compiles OK
>> >  f (Foo x _) = x
>> >
>> >instance (F (Foo b Char) ~ Char) => C (Foo b Char) where
>> >  f (Foo _ y) = y
>> >
>> > needs the eq constraint. Without it, GHC complains:
>> >Couldn't match expected type ‘F (Foo b Char)’
>> >with actual type ‘Char’
>> >Relevant bindings include
>> >  f :: Foo b Char -> F (Foo b Char)
>> >In the expression: y
>> >In an equation for ‘f’: f (Foo _ y) = y
>> >
>> > Note that if I change the sequence
>> > of the family instances for F,
>> > then GHC instead complains
>> > about the class instance for (Foo Int c).
>> >
>> > OK these are overlapping class instances.
>> > But GHC's usual behaviour
>> > (without closed type families)
>> > is to postpone complaining
>> > until and unless a usage
>> > (Foo Int Char) actually turns up.
>> >
>> > BTW if I put a first family instance
>> >  F (Foo Int Char) = Int
>> > to explicitly catch the overlap,
>> > then GHC complains about **both** class instances.
>> >
>> > Reminder [to Richard]
>> > I need not only types but also terms.
>> >
>> > AntC
>> > ___
>> > Glasgow-haskell-users mailing list
>> > Glasgow-haskell-users@haskell.org
>> > http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users
>> >
>>
>> ___
>> Glasgow-haskell-users mailing list
>> Glasgow-haskell-users@haskell.org
>> http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users
>>
>
>
> ___
> Glasgow-haskell-users mailing list
> Glasgow-haskell-users@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users
>
>
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users


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" 
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
> package in a nontrivial way (and I think it breaks HList too).

Hlist 0.4 released a couple weeks ago works around #10009 by using FDs
instead. User code isn't affected since the extra parameters are hidden by
using the original TF. But that won't help if you were using those TFs with
a gadt.
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users


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:
>
> > {-# LANGUAGE TypeFamilies #-}
> >
> > type family F a :: *
> >
> > type family G b :: *
> >
> > x :: G (F a) ~ a => F a
> > x = undefined
>
> GHC 7.10.1 reports:
>
> > Could not deduce (F a0 ~ F a)
> > from the context (G (F a) ~ a)
> >   bound by the type signature for x :: (G (F a) ~ a) => F a
> >   at Test.hs:7:6-23
> > NB: ‘F’ is a type function, and may not be injective
> > The type variable ‘a0’ is ambiguous
> > In the ambiguity check for the type signature for ‘x’:
> >   x :: forall a. (G (F a) ~ a) => F a
> > To defer the ambiguity check to use sites, enable AllowAmbiguousTypes
> > In the type signature for ‘x’: x :: G (F a) ~ a => F a
>
> At a first look, this complaint seems reasonable, and I have already
> wondered why GHC 7.8.3 actually accepts the above code.
>
> From an intuitive standpoint, however, the code seems actually
> acceptable to me. While it is true that type families are generally not
> injective, it is possible to derive the type a from F a by applying G.
>
> It would great if this code would be accepted by GHC again and if there
> was a workaround to make it work with GHC 7.10.1. At the moment, this
> change in the type checker from 7.8.3 to 7.10.1 breaks the
> incremental-computing package in a rather fundamental way.
>
> All the best,
> Wolfgang
>
> ___
> Glasgow-haskell-users mailing list
> Glasgow-haskell-users@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users
>
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users


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 
wrote:

> People,
>
> I wrote recently about finding places to set {-# OVERLAPPING #-}
> when porting an application from 7.8.2 to 7.10.1.
>
> I am doing this for porting  docon-2.12  from 7.8.2 to 7.10.1.
>
> And  ghc-7.10.1  indeed helped me to find several places to set this
> pragma (instead of using the total key -XOverlappingInstances).
>
> Finally, it has come to this module:
>
> -
> Preprocessing library docon-2.12.1...
> [48 of 86] Compiling ResRing__  ( ResRing__.hs, dist/build/ResRing__.o )
>
> ResRing__.hs:183:31:
> Overlapping instances for Eq (Maybe PropValue)
>   arising from a use of ‘/=’
> Matching instances:
>   instance Eq a => Eq (Maybe a) -- Defined in ‘GHC.Base’
>   instance (Residue r, Eq a) => Eq (r a) -- Defined in ‘ResEuc0_’
> In the expression: lookup IsGxBasis ps /= Just Yes
> ...
> --
>
> As before, I set
>instance {-# OVERLAPPING #-} (Residue r, Eq a) => Eq (r a)  where
> ...
>
> in  ResEuc0_.hs.
>
> But this does not help, the compiler continues with the same report.
>
> I see the difference to previous porting process in that one of the
> overlapping instances is of the GHC library, so that I cannot set the
> needed overlap pragma for it.
>
> On the other hand, ghc-7.8.2 compiled docon-2.12 successfully.
>
> What my be a way out?
>
> Thanks,
>
> --
> Sergei
>
>
> ___
> Glasgow-haskell-users mailing list
> Glasgow-haskell-users@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users
>
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users


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. If you don't mind naming the constructor
twice, you can do an "update" with:

myC = case defC of
C { .. } -> C { .. }
  where a = 2
-- myC == C 2 2 3

-- where we have for example
data CType = C { a, b, c :: Int } deriving Show
defC = C 1 2 3

If CType had multiple constructors, I think you'd be better off doing
the update with NamedFieldPuns syntax (defC { a }), or ordinary update
syntax (defC { a = 2 }).

Regards,
Adam


Regards,
Adam

On Tue, Feb 24, 2015 at 9:05 PM, Ben Franksen  wrote:
> I just noted that code like
>
> my_config = default_config {..} where
>   name = "my project"
>   description = "some longer text"
>
> gives me a syntax error, even if I have NamedFieldPuns and RecordWildCards
> extensions enabled. It seems that these extensions only work for record
> constructors and not for updating values.
>
> Is there a special reason puns/wildcards are not allowed in record updates?
>
> Cheers
> Ben
> --
> "There are two ways of constructing a software design: One way is to
> make it so simple that there are obviously no deficiencies and the other
> way is to make it so complicated that there are no obvious deficiencies.
> The first method is far more difficult."   ― C.A.R. Hoare
>
>
> ___
> Glasgow-haskell-users mailing list
> Glasgow-haskell-users@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users


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 never sees anything from line 19, when I uncomment it. Is
there something I can do to make that L19 work? Is this a known or
intentional limitation of type checker plugins?

Thanks,
Adam
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users


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
http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users


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  wrote:
> Hi Adam,
>
> It's great to hear that you are trying the plugins functionality, this
> is exactly the kind of experimentation it's designed for! I'm a little
> confused about what you're trying to achieve, though. Can you give some
> examples of code you'd like to be able to write?
>
> In general, GHC's type inference algorithm isn't expecting wanted
> constraints to be produced from givens; confusing things will happen if
> they are, and it's likely that *less* things will be typeable rather
> than *more*. Perhaps the plugin infrastructure should prevent you from
> doing so.
>
> It makes sense to produce givens from givens or wanteds from wanteds
> though. I'd imagine you might want to look for *wanted* constraints
> (HLength x ~ HLength y) and add an additional *wanted* (SameLength x y).
>
> One other thing to note is that plugins are called twice, once to
> simplify the givens (with empty wanteds), and once to solve the wanteds
> (https://ghc.haskell.org/trac/ghc/wiki/Plugins/TypeChecker#Callingpluginsfromthetypechecker).
>
> Hope this helps,
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users


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:
Could not deduce (SameLength y x) arising from an application
from the context (HLength x ~ HLength y)
  bound by the inferred type of
   p :: (HLength x ~ HLength y) => Proxy '(y, x)
  at a.hs:11:1-69

I think ghc should be able to figure out p :: (SameLength x y, HLength
x ~ HLength y) => Proxy '(x,y).

The code is self-contained:

git clone https://github.com/aavogt/HListPlugin

cd HListPlugin/ex

make


Is this approach supposed to be possible, or am I supposed to rewrite
things such that I only produce CtGivenS from the plugin?

Regards,
Adam
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


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  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 help here?

I agree it's not injective. But my impression is that injective TFs
pretty much allow ghc to replace a constraint

 TF a b ~ result

with

 (TF_getResult a b ~ result, TF_getB result a ~ b)

Where instances of:

type family TF a b | result a -> b, a b -> result -- or whatever the
notation actually is

define instances of ordinary type families TF_getB and TF_getResult.

So it's a move in the same direction to replace (HLength x ~ HLength
y) with SameLength x y. While I don't know how the code for SameLength
might be derived from the definition of HLength, that substitution
seems safe so long as (HLength x ~ HLength y) is still checked. I can
see that substitution happening in a type checker plugin, but it would
be nice if it was part of the language.

Regards,
Adam
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


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) ': HZipR xs ys

If there was no need to write some additional type families that tell
ghc how to find x and y given HZipR x y, then the version using TFs
might be as good as the version using FDs (defined in HList.hs)


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.
Copy-paste into ghci:

:set +t -XDataKinds -XFlexibleContexts -XTypeFamilies
import Data.HList
let desired = Proxy :: SameLength x '[(),()] => Proxy x
let current = Proxy :: (HLength y ~ HLength '[(),()]) => Proxy y

Prints

desired :: Proxy '[y, y1]
current :: HLength y ~ 'HSucc ('HSucc 'HZero) => Proxy y


Regards,
Adam


On Mon, Feb 9, 2015 at 10:58 AM, Jan Stolarek  wrote:
> Haskellers,
>
> I am finishing work on adding injective type families to GHC. I know that in 
> the past many people
> have asked for this feature. If you have use cases for injective type 
> families I would appreciate
> if you could show them to me. My implementation has some restrictions and I 
> want to see how
> severe these restrictions are from a practical point of view.
>
> Janek
>
> ---
> Politechnika Łódzka
>
> Treść tej wiadomości zawiera informacje przeznaczone tylko dla adresata.
> Jeżeli nie jesteście Państwo jej adresatem, bądź otrzymaliście ją przez 
> pomyłkę
> prosimy o powiadomienie o tym nadawcy oraz trwałe jej usunięcie.
> ___
> Haskell-Cafe mailing list
> haskell-c...@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


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 same as reify, except definitions that
are out of scope are either missing or modified such that they use
NameQ instead of NameG for out-of-scope names.

That way there is no new syntax needed, and safe TH can be called by
unsafe TH without any conversions.

I think defining another monad like Q that can do less is too
inconvenient because you have to disambiguate between Safe.listE and
Unsafe.listE, or make those functions more polymorphic (which makes
type errors worse). Another option would be if there were

newtype QThat (canIO :: Bool) (canReify :: Bool) (canNewName :: Bool)
   = QThat (TheRealQImplementation)

type Q = QThat True True True

listE :: Monad m => [m Exp] -> m Exp
listE = liftM ListE . sequence

reify :: Name -> QThat a True b Info
runIO :: IO a -> QThat True b c a

runQFFF :: QThat False False False a -> a
runQTFF :: QThat True False False a -> IO a


But I think that design would be a step in the direction of "harder to
reason about"

Regards,
Adam


On Fri, Jan 30, 2015 at 6:39 PM, Greg Weber  wrote:
> Hello GHC friends!
>
> I am starting up a proposal for variants of Template Haskell that restrict
> what operations are available. The goal is to make TH easier for users to
> reason about and to allow for an easier compilation story.
>
> Here is the proposal page:
> https://ghc.haskell.org/trac/ghc/wiki/TemplateHaskell/Restricted
>
> Right now the proposal does not have any details and the goal is to write
> out a clear specification.
> If this sounds interesting to you, let me know or leave some feedback on the
> wiki.
>
>
> Thanks,
> Greg Weber
>
>
>
> ___
> Glasgow-haskell-users mailing list
> Glasgow-haskell-users@haskell.org
> http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
>
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


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  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
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


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 (undefined :: F a) -- :: a


ghc-7.10.0.20141222 does not accept the program unless I uncomment the
type signature (a :: a).


I believe this is the main difference that prevents HList from
compiling with 7.10, but I could have made a mistake in coming up with
this minimal example.

Regards,
Adam
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


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 package (here:
http://hackage.haskell.org/package/unix-2.7.0.1/docs/System-Posix-Process.html#t:ProcessStatus,
with Carter's code): somebody else might define the same orphan
instance too, which will break programs that end up seeing both
instances.

Regards,
Adam

On Tue, Aug 5, 2014 at 12:49 PM, Carter Schonwald
 wrote:
> more concretely
> #if defined(__GLASGOW_HASKELL__) && ( __GLASGOW_HASKELL__ >= 707)
>  --- do the deriving version here
> #else
> --- your current stuff
> #endif
>
>
> On Tue, Aug 5, 2014 at 12:46 PM, Carter Schonwald
>  wrote:
>>
>> i assume 7.6 and 7.8, if we're talking GHC rather than GCC :)
>>
>> in 7.8 you can't define userland typeable instances, you need only write
>> deriving (Typeable) and you're all set.
>> add some CPP to select the instances suitable
>>
>>
>> On Tue, Aug 5, 2014 at 12:41 PM, Volker Wysk 
>> wrote:
>>>
>>> Hi!
>>>
>>> I've been working with GHC-4.6.3, and updating to GHC-4.8.3 breaks my
>>> code,
>>>
>>> because the Typeable class has been changed. The compiler produces this
>>>
>>> message:
>>>
>>> -
>>>
>>> src/HsShellScript/ProcErr.chs:2294:4:
>>>
>>> ‘typeOf’ is not a (visible) method of class ‘Typeable’
>>>
>>> -
>>>
>>> I want to define System.Posix.Process.ProcessStatus to be an instance of
>>>
>>> Typeable, so I can throw and catch it as an exception. ProcessStatus
>>> isn't
>>>
>>> typeable by default.
>>>
>>> Is it still possible to make ProcessStatus a member of Typeable? How?
>>>
>>> Obviously, you can't accomplish it by deriving Typeable, because the
>>> definition
>>>
>>> can't be changed any longer.
>>>
>>> This is the spot in question:
>>>
>>> --
>>>
>>> import System.Posix.Process
>>>
>>> import Data.Typeable
>>>
>>> {-
>>>
>>> data ProcessStatus = Exited ExitCode
>>>
>>>| Terminated Signal
>>>
>>>| Stopped Signal
>>>
>>>deriving (Eq, Ord, Show)
>>>
>>> -}
>>>
>>> instance Typeable ProcessStatus where
>>>
>>>typeOf = const tyCon_ProcessStatus
>>>
>>> tyCon_ProcessStatus = mkTyConApp (mkTyCon3 "hsshellscript"
>>>
>>>"HsShellScript.ProcErr"
>>>
>>>"Posix.ProcessStatus") []
>>>
>>> instance Exception ProcessStatus
>>>
>>> --
>>>
>>> Thanks,
>>>
>>> V.W.
>>>
>>>
>>> ___
>>> Glasgow-haskell-users mailing list
>>> Glasgow-haskell-users@haskell.org
>>> http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
>>>
>>
>
>
> ___
> Glasgow-haskell-users mailing list
> Glasgow-haskell-users@haskell.org
> http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
>
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


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  wrote:
> Actually, I was looking into it a little, and template haskell could
> effectively be implemented by a pre-processor and a portable library
> that is compiler independent. If one could get ghc to spit out the
> template haskell source after it expands it then that can be fed to
> jhc as a quick first pass, but ideally the pre-processor TH would
> create programs that can be run under the target compiler. that would
> bring TH to every haskell compiler.
>
> John
>
> On Sat, Jul 5, 2014 at 10:38 AM, Brandon Allbery  wrote:
>> On Sat, Jul 5, 2014 at 1:34 PM, Carter Schonwald
>>  wrote:
>>>
>>> does JHC support template haskell?
>>
>>
>> Pretty sure TH is too closely tied to ghc.
>>
>> --
>> brandon s allbery kf8nh   sine nomine associates
>> allber...@gmail.com  ballb...@sinenomine.net
>> unix, openafs, kerberos, infrastructure, xmonadhttp://sinenomine.net
>
>
>
> --
> John Meacham - http://notanumber.net/
> ___
> Glasgow-haskell-users mailing list
> Glasgow-haskell-users@haskell.org
> http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


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 http://code.haskell.org/~aavogt/HList/
 cd HList
 cabal install -fnew_type_eq

When I select instance (B) instead by uncommenting the alternative
instance in Data/HList/FakePrelude.hs, one of the more informative
type errors suggests that the == type family is getting stuck:

Data/HList/Variant.hs:202:29: Warning:
Could not deduce (HasField'
(l Data.Type.Equality.== l) l (Tagged l (Maybe
e) : v) (Maybe e))
  arising from a use of ‘mkVariant’
from the context (ConvHList p,
  SameLength' v v,
  HMapCxt HMaybeF p v,
  le ~ Tagged l (Maybe e))

Does this suggest that type (==) should work with all kinds, as it would with:

> type a == b = Proxy a `EqStar` Proxy b

https://github.com/ghc/packages-base/blob/master/Data/Type/Equality.hs
mentions "A poly-kinded instance is /not/ provided, as a recursive
definition for algebraic kinds is generally more useful.", but are
there instances of (==) that behave differently from the poly-kinded
version?

Regards,
Adam
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


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 imagine that would lead to harder-to-fix breakage than #8883,
but on the other hand type signatures in let/where are pretty rare.

Regards,
Adam
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


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
 wrote:
> I want to import Nat and type-level (<=) from GHC.TypeLits:
>
>   import GHC.TypeLits (Nat, (<=))
>
> "Nat" is found this way, but (<=) is not:
>
>   Module ‘GHC.TypeLits’ does not export ‘(<=)’
>
> What is the trick?
>
> The doc only shows the anonymous import:
>
> http://www.haskell.org/ghc/docs/7.8.1-rc2/html/users_guide/promotion.html
> ___
> Glasgow-haskell-users mailing list
> Glasgow-haskell-users@haskell.org
> http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


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
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


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
 wrote:
> I was trying to fix one of my closed type families examples for the new 
> syntax, and run into an unfortunate issue. Due to a kind error in my code one 
> of my constraints was being silently discarded (see ticket: 
> https://ghc.haskell.org/trac/ghc/ticket/8669)
>
> The main reason I resorted to this (in hindsight) ill-kinded hack is the lack 
> of a vacuous (i.e. never holding) constraint to produce type errors. I would 
> love to be able to explicitly force GHC into realising "this constraint can 
> never hold", if I had the ability to pass along a String/Symbol to be 
> reported to the user, that would be even better.
>
> Cheers,
> Merijn
>
> ___
> Glasgow-haskell-users mailing list
> Glasgow-haskell-users@haskell.org
> http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
>
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


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 are the type signatures needed? If I leave all of them off, I get:

Could not deduce (C a1 a0)
  arising from the ambiguity check for ‛c2’
from the context (C a b, C a1 a)
  bound by the inferred type for ‛c2’: (C a b, C a1 a) => a1 -> b

from the line: c2 x = c (c x)


From my perspective, it seems that the type signature ghc infers
should be able to restrict the ambiguous types as the hand-written
signature does.

These concerns apply to HEAD (using -XAllowAmbiguousTypes) and ghc-7.6 too.

Regards,
Adam
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users