[Haskell-cafe] using type variables in type declarations inside function

Li-yao Xia lysxia at gmail.com
Thu Apr 12 19:50:34 UTC 2018


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.
> 


More information about the Haskell-Cafe mailing list