using type variables in type declarations inside function

Let's say I've written a function on three types. myFunc :: a -> b -> c myFunc x y z = ... where helper :: a -> [b] helper xx = ... Notice that I'm attempting to declare 'helper' using my type variables. I've noticed that this results in an error. Is this actually possible, and how? D

Hi Dennis, Use ScopedTypeVariables. {-# LANGUAGE ScopedTypeVariables #-} myFunc :: forall a b c. a -> b -> c -- explicit binders ... helper :: a -> [b] On 04/12/2018 03:47 PM, Dennis Raddle wrote:
Let's say I've written a function on three types.
myFunc :: a -> b -> c myFunc x y z = ... where helper :: a -> [b] helper xx = ...
Notice that I'm attempting to declare 'helper' using my type variables. I've noticed that this results in an error.
Is this actually possible, and how?
D
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.

On Thu, Apr 12, 2018 at 3:47 PM, Dennis Raddle
myFunc :: a -> b -> c myFunc x y z = ... where helper :: a -> [b] helper xx = ...
Notice that I'm attempting to declare 'helper' using my type variables. I've noticed that this results in an error. Is this actually possible, and how?
You need the ScopedTypeVariables extension, *and* to "declare" the type variables whose scope is to be extended with an explicit "forall" in the signature. -- brandon s allbery kf8nh sine nomine associates allbery.b@gmail.com ballbery@sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net

Thanks!
By the way, why do I sometimes have to use forall, and sometimes not?
I'm also learning Purescript, and I noticed that the examples use 'forall'
in every case. Why would it be different with Purescript?
D
On Thu, Apr 12, 2018 at 12:51 PM, Brandon Allbery
On Thu, Apr 12, 2018 at 3:47 PM, Dennis Raddle
wrote: myFunc :: a -> b -> c myFunc x y z = ... where helper :: a -> [b] helper xx = ...
Notice that I'm attempting to declare 'helper' using my type variables. I've noticed that this results in an error. Is this actually possible, and how?
You need the ScopedTypeVariables extension, *and* to "declare" the type variables whose scope is to be extended with an explicit "forall" in the signature.
-- brandon s allbery kf8nh sine nomine associates allbery.b@gmail.com ballbery@sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net

I don't know Purescript so couldn't say about that. In standard Haskell you
don't need to use forall at all; it's used by this extension and by
extensions for existential types.
On Thu, Apr 12, 2018 at 4:24 PM, Dennis Raddle
Thanks!
By the way, why do I sometimes have to use forall, and sometimes not?
I'm also learning Purescript, and I noticed that the examples use 'forall' in every case. Why would it be different with Purescript? D
On Thu, Apr 12, 2018 at 12:51 PM, Brandon Allbery
wrote: On Thu, Apr 12, 2018 at 3:47 PM, Dennis Raddle
wrote: myFunc :: a -> b -> c myFunc x y z = ... where helper :: a -> [b] helper xx = ...
Notice that I'm attempting to declare 'helper' using my type variables. I've noticed that this results in an error. Is this actually possible, and how?
You need the ScopedTypeVariables extension, *and* to "declare" the type variables whose scope is to be extended with an explicit "forall" in the signature.
-- brandon s allbery kf8nh sine nomine associates allbery.b@gmail.com ballbery@sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net
-- brandon s allbery kf8nh sine nomine associates allbery.b@gmail.com ballbery@sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net

On Thu, Apr 12, 2018 at 04:26:50PM -0400, Brandon Allbery wrote:
I don't know Purescript so couldn't say about that. In standard Haskell you don't need to use forall at all; it's used by this extension and by extensions for existential types.
RankNTypes too iirc

I too am curious about the forall in ScopedTypeVariables. It seems formally
unnecessary, so I assume it is designed to avert some kind of inconsistency
with standard behavior? Thinking about other extensions, e.g.
FlexibleInstances or MultiParamTypeClasses, it seems like they all give
meaning to constructs that are forbidden by the standard, while this one
actually changes the standard behavior (for the better, imho) and so
requires protection by some nonstandard signifier, i.e. forall.
On Apr 12, 2018 13:27, "Dennis Raddle"
On Thu, Apr 12, 2018 at 3:47 PM, Dennis Raddle
wrote: myFunc :: a -> b -> c myFunc x y z = ... where helper :: a -> [b] helper xx = ...
Notice that I'm attempting to declare 'helper' using my type variables. I've noticed that this results in an error. Is this actually possible, and how?
You need the ScopedTypeVariables extension, *and* to "declare" the type variables whose scope is to be extended with an explicit "forall" in the signature.
-- brandon s allbery kf8nh sine nomine associates allbery.b@gmail.com ballbery@sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.

It's just compatibility with the standard: there might be existing code
that depends on Haskell 98 not extending the scope of a type variable, so
you need to be explicit about which type variables' scope to extend.
"forall" is already there for other extensions, and is otherwise a no-op in
this situation, so it's a safe way to specify the extended scope.
On Thu, Apr 12, 2018 at 4:41 PM, Ryan Reich
I too am curious about the forall in ScopedTypeVariables. It seems formally unnecessary, so I assume it is designed to avert some kind of inconsistency with standard behavior? Thinking about other extensions, e.g. FlexibleInstances or MultiParamTypeClasses, it seems like they all give meaning to constructs that are forbidden by the standard, while this one actually changes the standard behavior (for the better, imho) and so requires protection by some nonstandard signifier, i.e. forall.
On Apr 12, 2018 13:27, "Dennis Raddle"
wrote: Thanks!
By the way, why do I sometimes have to use forall, and sometimes not?
I'm also learning Purescript, and I noticed that the examples use 'forall' in every case. Why would it be different with Purescript? D
On Thu, Apr 12, 2018 at 12:51 PM, Brandon Allbery
wrote: On Thu, Apr 12, 2018 at 3:47 PM, Dennis Raddle
wrote: myFunc :: a -> b -> c myFunc x y z = ... where helper :: a -> [b] helper xx = ...
Notice that I'm attempting to declare 'helper' using my type variables. I've noticed that this results in an error. Is this actually possible, and how?
You need the ScopedTypeVariables extension, *and* to "declare" the type variables whose scope is to be extended with an explicit "forall" in the signature.
-- brandon s allbery kf8nh sine nomine associates allbery.b@gmail.com ballbery@sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.
-- brandon s allbery kf8nh sine nomine associates allbery.b@gmail.com ballbery@sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net

It could still be useful in local definitions. Like
something :: a -> ...
something =
let somethinElse :: forall b. b -> a -> ...
Az iPademről küldve
2018. ápr. 12. dátummal, 22:43 időpontban Brandon Allbery
It's just compatibility with the standard: there might be existing code that depends on Haskell 98 not extending the scope of a type variable, so you need to be explicit about which type variables' scope to extend. "forall" is already there for other extensions, and is otherwise a no-op in this situation, so it's a safe way to specify the extended scope.
On Thu, Apr 12, 2018 at 4:41 PM, Ryan Reich
wrote: I too am curious about the forall in ScopedTypeVariables. It seems formally unnecessary, so I assume it is designed to avert some kind of inconsistency with standard behavior? Thinking about other extensions, e.g. FlexibleInstances or MultiParamTypeClasses, it seems like they all give meaning to constructs that are forbidden by the standard, while this one actually changes the standard behavior (for the better, imho) and so requires protection by some nonstandard signifier, i.e. forall. On Apr 12, 2018 13:27, "Dennis Raddle"
wrote: Thanks! By the way, why do I sometimes have to use forall, and sometimes not?
I'm also learning Purescript, and I noticed that the examples use 'forall' in every case. Why would it be different with Purescript? D
On Thu, Apr 12, 2018 at 12:51 PM, Brandon Allbery
wrote: On Thu, Apr 12, 2018 at 3:47 PM, Dennis Raddle
wrote: myFunc :: a -> b -> c myFunc x y z = ... where helper :: a -> [b] helper xx = ... Notice that I'm attempting to declare 'helper' using my type variables. I've noticed that this results in an error. Is this actually possible, and how?
You need the ScopedTypeVariables extension, *and* to "declare" the type variables whose scope is to be extended with an explicit "forall" in the signature.
-- brandon s allbery kf8nh sine nomine associates allbery.b@gmail.com ballbery@sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.
-- brandon s allbery kf8nh sine nomine associates allbery.b@gmail.com ballbery@sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net _______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.
participants (6)
-
Brandon Allbery
-
Dennis Raddle
-
Francesco Ariis
-
Li-yao Xia
-
MigMit
-
Ryan Reich