Re: New GHC feature proposal: Pattern families

2014-06-29 Thread Baldur Blöndal
Yes I reported #9226 :)

I created a wiki page for pattern families
(https://ghc.haskell.org/trac/ghc/wiki/PatternFamilies) with a whole
host of examples, trying to keep them simple so do let me know it
anything is unclear.

In the area of pattern synonyms I agree with testing the waters a bit,
personally I'd like to change the syntax since it doesn't really scale
for using complicated view patterns (forcing you to define auxiliary
functions) and looks a bit awkward when adding type annotations and
explicitely bidirectional patterns.

I'd say explicitely bidirectional patterns are the next step forward
but it depends on the priorities:
· End users: Explicitely bidirectional patterns (#8581) and associated
pattern synonyms (#8583) are the biggest two, although the latter can
be ‘faked’ with type classes: If #8581/#8583 are implemented and if
(:)/[] weren't built-in syntax libraries like Data.Text could be used
as a drop-in replacement for String, currently users must change every
pattern match to a case statement (but I digress)
· Library authors: Exhaustiveness checks (#8779) are important for
getting abstract data types on par with normal data types.

Since you mentioned VPA (ViewPatternsAlternative) I took the liberty
of using several examples from the VPA wiki page and contrasting them
with the example found there, most of the ones I did not mention (like
“join lists”) can be implemented using PatternSynonyms, I feel some of
the VPA examples are better motivating examples than what I presented
before.

Best regards,
Baldur


2014-06-29 9:40 GMT+02:00, Baldur Blöndal :
> Yes I reported #9226 :)
>
> I created a wiki page for pattern families
> (https://ghc.haskell.org/trac/ghc/wiki/PatternFamilies) with a whole
> host of examples, trying to keep them simple so do let me know it
> anything is unclear.
>
> In the area of pattern synonyms I agree with testing the waters a bit,
> personally I'd like to change the syntax since it doesn't really scale
> for using complicated view patterns (forcing you to define auxiliary
> functions) and looks a bit awkward when adding type annotations and
> explicitely bidirectional patterns.
>
> I'd say explicitely bidirectional patterns are the next step forward
> but it depends on the priorities:
> · End users: Explicitely bidirectional patterns (#8581) and associated
> pattern synonyms (#8583) are the biggest two, although the latter can
> be ‘faked’ with type classes: If #8581/#8583 are implemented and if
> (:)/[] weren't built-in syntax libraries like Data.Text could be used
> as a drop-in replacement for String, currently users must change every
> pattern match to a case statement (but I digress)
> · Library authors: Exhaustiveness checks (#8779) are important for
> getting abstract data types on par with normal data types.
>
> Since you mentioned VPA (ViewPatternsAlternative) I took the liberty
> of using several examples from the VPA wiki page and contrasting them
> with the example found there, most of the ones I did not mention (like
> “join lists”) can be implemented using PatternSynonyms, I feel some of
> the VPA examples are better motivating examples than what I presented
> before.
>
> Best regards,
> Baldur
>
> 2014-06-23 17:30 GMT+02:00, Edward Kmett :
>> The main thing Baldur had asked me about was if it makes sense to talk
>> about patterns that are parameterized by expressions in places.
>>
>> I agree that the thought is very poorly fleshed out, but as a motivation,
>> in some sense the previous form of view patterns already do this.
>>
>> Consider (->), which takes in an expression to apply on the left and a
>> pattern for what to match against the result of it on the right.
>>
>> The question then becomes can we allow this for arbitrary patterns?
>>
>> There are a number of use cases for these. For example,
>>
>> A pattern to match a regular expression might look like
>>
>> Foo (x :~= "ab*")
>>
>> where you want "ab*" to be passed as a parameter to the code for the
>> pattern synonym (:~=), not be something it is binding.
>>
>> This then speaks to needing some notion of mode for the different
>> parameters.
>>
>> One of the reasons I'm under-excited about pattern synonyms is we already
>> built all the machinery for working with prisms in lens to generalize
>> them.
>> =)
>>
>> In lens we have a combinator 'preview :: Prism' s a -> s -> Maybe a'.
>>
>> As a straw man proposal:
>>
>> It'd be nice to be able to do something like
>>
>> pattern (Match p a) <- (preview p -> Just a)
>>
>> and have it take the arguments that go to the left ha

Coding style: Using StandaloneKindSignatures in GHC

2021-05-18 Thread Baldur Blöndal
Discussion to permit use of StandaloneKindSignatures in the GHC coding
style guide. I believe it increases the clarity of the code,
especially as we move to fancier kinds.

It is the only way we have for giving full signatures to type
synonyms, type classes, type families and others. An example:

type Cat :: Type -> Type
type Cat ob = ob -> ob -> Type

type  Category :: forall ob. Cat ob -> Constraint
class Category cat where
  id :: cat a a ..

type Proxy :: forall k. k -> Type
data Proxy a = Proxy

type Some :: forall k. (k -> Type) -> Type
data Some f where
  Some :: f ex -> Some f

-- | The regular function type
type (->) :: forall {rep1 :: RuntimeRep} {rep2 :: RuntimeRep}.
TYPE1 rep1 -> TYPE rep2 -> Type
type (->) = FUN 'Many

This is in line with function definitions that are always given a
top-level, standalone type signature (1) and not like we currently
define type families/synonyms (2) by annotating each argument or not
at all. Using -XStandaloneKindSignatures (3) matches (1)

-- (1)
curry :: ((a, b) -> c) -> (a -> b -> c)
curry f  x y = f (x, y)

-- (2)
type Curry (f :: (a, b) -> c) (x :: a) (y :: b) =  f '(x, y) :: c

-- (3)
type Curry :: ((a, b) -> c) -> (a -> b -> c)
type Curry f x y = f '(x, y)

It covers an edgecase that `KindSignatures` don't. The only way for
deriving to reference datatype arguments is if they are quantified by
the declaration head -- `newtype Bin a ..`. StandaloneKindSignatures
allows us to still provide a full signature. We could write `newtype
Bin a :: Type -> Type` without it but not `newtype Bin :: Type -> Type
-> Type`

typeBin :: Type -> Type -> Type
newtype Bin a b = Bin (a -> a -> b)
  deriving (Functor, Applicative)
  via (->) a `Compose` (->) a

Let me know what you think
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Coding style: Using StandaloneKindSignatures in GHC

2021-05-20 Thread Baldur Blöndal
> encouraging the use of a standalone signature for type declarations where at 
> least one parameter of the datatype does not have kind Type.

So Dict, Eq both get a sig but Fix and Either do not?

  type Dict :: Constraint -> Type
  type Eq   :: Type -> Constraint
  type Fix  :: (Type -> Type) -> Type

It's sensible to exclude tired tropes like `Type` and `Type -> Type`
but higher-order functors (like Fix) warrant a signature.

Caveat: The kind of type synonyms, type families and data families is
not necessarily determined by counting the syntactic arguments of X
like for a `data' declaration as Y could be a type, a functor, a
bifunctor..

  type X = Y
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Give MonadTrans a QuantifiedConstraints superclass

2021-06-01 Thread Baldur Blöndal
This is to advertise the proposal
(https://gitlab.haskell.org/ghc/ghc/-/issues/19922) to add a
superclass to the MonadTrans type class in Control.Monad.Trans.

A Monad transformer 'trans' lifts a 'Monad m' to a 'Monad (trans m)'.

This proposal code-ifies that with a superclass constraint, an
impliciation constraint enabled by the recent extension
QuantifiedConstraints:

class (forall m. Monad m => Monad (trans m)) => MonadTrans trans where
  ..

This is the main motiviating example of the Quantified Class
Constraints paper https://gkaracha.github.io/papers/quantcs.pdf
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Moving ArgumentsDo forward

2016-06-01 Thread Baldur Blöndal
This gets a guilty +1 from me, I have always found $ busy and
cumbersome to read. Patterns such as  ‘f a b c $ do’ are ubiquitous
(especially in ESDLs where clean syntax matters more) and code such as

> dataFetch req = Fetch $ \ref -> do

awkwardly requires 3 steps ($, lambda, do).

2016-06-01 16:32 GMT, Edward Kmett :
> Just as a note: I noticed this was being discussed a couple of weeks ago as
> a possible topic for haskell-prime, when they were discussing what was in
> scope for the committee, so I'm not entirely sure its a dead topic.
>
> -Edward
>
> On Wed, Jun 1, 2016 at 11:09 AM, Bardur Arantsson 
> wrote:
>
>> On 06/01/2016 01:48 PM, Akio Takano wrote:
>> > Hi,
>> >
>> > Ticket #10843 [0] proposes an extension, ArgumentsDo, which I would
>> > love to see in GHC. It's a small syntactic extension that allows do,
>> > case, if and lambda blocks as function arguments, without parentheses.
>> > However, its differential revision [1] has been abandoned, citing a
>> > mixed response from the community. A message [2] on the ticket
>> > summarizes a thread in haskell-cafe on this topic.
>> >
>> > I, for one, think adding this extension is worthwhile, because a
>> > significant number of people support it. Also, given how some people
>> > seem to feel ambivalent about this change, I believe actually allowing
>> > people to try it makes it clearer whether it is a good idea.
>> >
>> > Thus I'm wondering: is there any chance that this gets merged? If so,
>> > I'm willing to work on whatever is remaining to get the change merged.
>> >
>>
>> What's changed since it was last discussed? I don't think the objections
>> were centered in the implementation, so I don't see what "whatever is
>> remaining to get the change merged" would be.
>>
>> AFAICT at best it's a *very* small improvement[1] and fractures Haskell
>> syntax even more around extensions -- tooling etc. will need to
>> understand even *more* syntax extensions[2].
>>
>> Regards,
>>
>> [1] If you grant that it is indeed an improvment, which I, personally,
>> don't think it is.
>>
>> [2] I think most people agree that this is something that should perhaps
>> be handled by something like
>> https://github.com/haskell/haskell-ide-engine so that it would only need
>> to be implemented once, but there's not even an alpha release yet, so
>> that particular objection stands, AFAICT.
>>
>>
>> ___
>> ghc-devs mailing list
>> ghc-devs@haskell.org
>> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>>
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Request for feedback: deriving strategies syntax

2016-08-18 Thread Baldur Blöndal
I haven't followed the thread but do we actually need a name for it, can't
it be indicated by omission?
‘default’ or ‘builtin’ sounds okay

2016-08-18 20:00 GMT+00:00 Nicolas Frisby :

> The Report specifies the semantics of most (all other than Generic?)
> derivation strategies that are baked-in to the compiler.
>
> https://www.haskell.org/onlinereport/haskell2010/
> haskellch11.html#x18-18200011
>
> I think this raises an issue of what *exactly* we are currently referring
> to as "bespoke". E.G. can it vary with the precise compiler being used?
> (Maybe your wiki page addresses this; I haven't clicked through.)
>
> But maybe "language-report" would supplant "bespoke". And perhaps
> "GHC-7.8" would also make sense, if the baked-in derivation scheme varies
> from the report's spec? Etc.
>
> HTH. -Nick
>
> On Thu, Aug 18, 2016, 12:24 Elliot Cameron  wrote:
>
>> Given the prevalence of spellings like "normalise" in common Haskell
>> packages, we might just be settling on British English. Being American
>> makes that a tad difficult on my end, but personally I can make peace with
>> it.
>>
>> On Thu, Aug 18, 2016 at 3:19 PM, Matthew Pickering <
>> matthewtpicker...@gmail.com> wrote:
>>
>>> I also like 'bespoke' but then it seems to be a much more common in
>>> British English than American English.
>>>
>>> On Thu, Aug 18, 2016 at 7:46 PM, Ryan Scott 
>>> wrote:
>>> > Bardur,
>>> >
>>> > Since you don't like "bespoke", would you mind suggesting an
>>> > alternative, or advocating for a previously mentioned idea? From [1],
>>> > the ideas I've seen tossed around are:
>>> >
>>> > * builtin
>>> > * standard (Elliot Cameron suggested it here [2])
>>> > * wiredin (Cater Schonwald suggested it here [3])
>>> > * magic (Andres Löh suggested it here [4])
>>> > * native
>>> > * original
>>> > * specialized (the above three are ad hoc suggestions I came up with
>>> in a hurry)
>>> >
>>> > Ryan S.
>>> > -
>>> > [1] https://ghc.haskell.org/trac/ghc/wiki/Commentary/Compiler/
>>> DerivingStrategies#Alternativesyntax
>>> > [2] https://mail.haskell.org/pipermail/ghc-devs/2016-July/012448.html
>>> > [3] https://mail.haskell.org/pipermail/ghc-devs/2016-July/012450.html
>>> > [4] https://mail.haskell.org/pipermail/ghc-devs/2016-July/012453.html
>>> > ___
>>> > ghc-devs mailing list
>>> > ghc-devs@haskell.org
>>> > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>>> ___
>>> ghc-devs mailing list
>>> ghc-devs@haskell.org
>>> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>>>
>>
>> ___
>> ghc-devs mailing list
>> ghc-devs@haskell.org
>> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>>
>
> ___
> ghc-devs mailing list
> ghc-devs@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Getting rid of -XImpredicativeTypes

2016-09-30 Thread Baldur Blöndal
Shot in the dark: Would extensions like QuantifiedConstraints or
ImplicationConstraints, if implemented, help with ImpredicativeTypes?

2016-09-30 15:29 GMT+00:00 Simon Peyton Jones via ghc-devs <
ghc-devs@haskell.org>:

> Alejandro: excellent point. I mis-spoke before.  In my proposal we WILL
> allow types like (Tree (forall a. a->a)).
>
>
>
> I’m trying to get round to writing a proposal (would someone else like to
> write it – it should be short), but the idea is this:
>
>
>
> *When you have -XImpredicativeTypes*
>
> · *You can write a polytype in a visible type argument; eg.  f
> @(forall a. a->a)*
>
> · *You can write a polytype as an argument of a type in a
> signature  e.g.  f :: [forall a. a->a] -> Int*
>
>
>
> *And that’s all.  A unification variable STILL CANNOT be unified with a
> polytype.  The only way you can call a polymorphic function at a polytype
> is to use Visible Type Application.*
>
>
>
> *So using impredicative types might be tiresome.  E.g.*
>
> *  type SID = forall a. a->a*
>
>
>
> *  xs :: [forall a. a->a]*
>
> *  xs = (:) @SID id ( (:) @SID id ([] @ SID))*
>
>
>
> *In short, if you call a function at a polytype, you must use VTA.
> Simple, easy, predictable; and doubtless annoying.  But possible*.
>
>
>
> Simon
>
>
>
> *From:* Alejandro Serrano Mena [mailto:trup...@gmail.com]
> *Sent:* 26 September 2016 08:13
> *To:* Simon Peyton Jones 
> *Cc:* ghc-us...@haskell.org; ghc-devs@haskell.org
> *Subject:* Re: Getting rid of -XImpredicativeTypes
>
>
>
> What would be the story for the types of the arguments. Would I be allowed
> to write the following?
>
> > f (lst :: [forall a. a -> a]) = head @(forall a. a -> a) lst 3
>
> Regards,
>
> Alejandro
>
>
>
> 2016-09-25 20:05 GMT+02:00 Simon Peyton Jones via ghc-devs <
> ghc-devs@haskell.org>:
>
> Friends
>
>
>
> GHC has a flag -XImpredicativeTypes that makes a half-hearted attempt to
> support impredicative polymorphism.  But it is vestigial…. if it works,
> it’s really a fluke.  We don’t really have a systematic story here at all.
>
>
>
> I propose, therefore, to remove it entirely.  That is, if you use
> -XImpredicativeTypes, you’ll get a warning that it does nothing (ie.
> complete no-op) and you should remove it.
>
>
>
> Before I pull the trigger, does anyone think they are using it in a
> mission-critical way?
>
>
>
> Now that we have Visible Type Application there is a workaround: if you
> want to call a polymorphic function at a polymorphic type, you can
> explicitly apply it to that type.  For example:
>
>
>
> {-# LANGUAGE ImpredicativeTypes, TypeApplications, RankNTypes #-}
>
> module Vta where
>
>   f x = id @(forall a. a->a) id @Int x
>
>
>
> You can also leave out the @Int part of course.
>
>
>
> Currently we have to use -XImpredicativeTypes to allow the @(forall a.
> a->a).Is that sensible?  Or should we allow it regardless?   I rather
> think the latter… if you have Visible Type Application (i.e.
> -XTypeApplications) then applying to a polytype is nothing special.   So I
> propose to lift that restriction.
>
>
>
> I should go through the GHC Proposals Process for this, but I’m on a
> plane, so I’m going to at least start with an email.
>
>
>
> Simon
>
>
> ___
> ghc-devs mailing list
> ghc-devs@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
> 
>
>
>
> ___
> ghc-devs mailing list
> ghc-devs@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Hunting down a compilation performance regression involving type families

2017-06-06 Thread Baldur Blöndal
This a use case for ImplicationConstraints, or what

On Jun 6, 2017 19:02, "David Feuer"  wrote:

> Edward Kmett has explained that this isn't sufficient when things go
> higher order. His suggested improvement is
>
> liftCoercion :: Maybe (Coercion a b -> Coercion (f a) (f b))
>
>
>
> David Feuer
> Well-Typed, LLP
>
>  Original message 
> From: Ryan Scott 
> Date: 6/6/17 1:41 PM (GMT-05:00)
> To: Richard Eisenberg 
> Cc: GHC developers , Eric Mertens <
> emert...@gmail.com>
> Subject: Re: Hunting down a compilation performance regression involving
> type families
>
> Hrm. It's a shame that supporting this map/coerce RULE causes such pain.
>
> This makes me wonder: can we get rid of this RULE? Eric Mertens pointed out
> a trick [1] that's used in the profunctors library to make mapping coerce
> over certain Profunctors more efficient. To adapt this trick for Functor,
> we'd need to add another class method:
>
> class Functor f where
> fmap :: (a -> b) -> f a -> f b
> (<#>) :: Coercible a b => (a -> b) -> f a -> f b
> (<#>) = \f -> \p -> p `seq` fmap f p
>
> Now, when implementing Functor instances, if we are working with a datatype
> whose role is representational or phantom, we can make (<#>) really fast:
>
> data List a = Nil | Cons a (List a)
> instance Functor List where
> fmap = ...
> (<#>) = coerce
>
> Now, instead of relying on (map MkNewtype Nil) to rewrite to Nil, we can
> just use (MkNewtype <#> Nil)! No map/coerce RULE necessary :)
>
> OK, I realize that suggesting that we remove the RULE is perhaps a touch
> too far. But it does sting that we have to pay hefty compilation penalties
> because of its existence...
>
> Ryan S.
> -
> [1]
> http://hackage.haskell.org/package/profunctors-5.2/docs/
> Data-Profunctor-Unsafe.html#v:-35-
> .
>
> On Wed, May 31, 2017 at 7:25 PM, Richard Eisenberg 
> wrote:
>
> >
> > > On May 31, 2017, at 5:21 PM, Ryan Scott 
> wrote:
> > > Does you know what might be going on here?
> >
> > I think so, but I don't know how to fix it.
> >
> > The commit you found (thank you!) makes simple_opt_expr (the "simple
> > optimizer", run directly after desugaring, even with -O0) a little more
> > selective in what `case` expressions it throws away. Previous to that
> > commit, the optimizer would throw away a `case error "deferred type
> error"
> > of _ -> ...` which is terrible. It seems that you have discovered that we
> > are now too timid in throwing away unhelpful cases. It would be
> interesting
> > to know what the newly-retained cases look like, so that we might throw
> > them away.
> >
> > But there remains a mystery: Why do we need this code at all? Reading
> Note
> > [Getting the map/coerce RULE to work] closely, it seems we need to
> simplify
> >
> >   forall a b (co :: a ~R# b).
> > let dict = MkCoercible @* @a @b co in
> > case Coercible_SCSel @* @a @b dict of
> >   _ [Dead] -> map @a @b (\(x :: a) -> case dict of
> >  MkCoercible (co :: a ~R# b) -> x |> co) = let dict = ... in ...
> >
> > to
> >
> >   forall a b (co :: a ~R# b).
> > map @a @b (\(x :: a) -> x |> co) = \(x :: [a]) -> x |> [co]
> >
> > Part of doing so is to drop the `case Coercible_SCSel ...`, which gets in
> > the way. The mystery is why this needs special code -- shouldn't the
> > eliminate-case-of-known-constructor do the trick? This would require
> > unfolding Coercible_SCSel. Does that happen? It would seem not... but
> maybe
> > it should, which would remove the special-case code that I changed in
> that
> > commit, and quite likely would simplify much more code besides.
> >
> > So: Is Coercible_SCSel unfolded during simple_opt? If not, what wonderful
> > or terrible things happen if we do? If so, why does
> > case-of-known-constructor not work here? My guess is that answering these
> > questions may solve the original problem, but this guess could be wrong.
> >
> > Richard
> >
> >
>
> ___
> ghc-devs mailing list
> ghc-devs@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs