[GHC] #15762: ghci command: report function's inferred visible type applications
GHC
ghc-devs at haskell.org
Wed Oct 17 15:03:22 UTC 2018
#15762: ghci command: report function's inferred visible type applications
-------------------------------------+-------------------------------------
Reporter: Iceland_jack | Owner: (none)
Type: feature request | Status: new
Priority: normal | Milestone:
Component: GHCi | Version: 8.6.1
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: #15610 #15613 | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Description changed by Iceland_jack:
Old description:
> Example inspired by #40.
>
> ghci already has a
> [https://downloads.haskell.org/~ghc/latest/docs/html/users_guide/ghci.html
> #ghci-cmd-:type-at :type-at] command for reporting a type in a range
>
> {{{
> >> :type-at X.hs 6 6 6 7 f
> Int -> Int
> }}}
>
> A similar thing (for integrating into IDEs) is doing the same for visible
> type applications. An innocent expression like `x y` has a lot going on
> under the surface
>
> {{{#!hs
> {-# Language RankNTypes #-}
> {-# Language PolyKinds #-}
> {-# Language KindSignatures #-}
>
> import Data.Kind
>
> f :: forall res
> . (forall k (f :: k -> Type) (a :: k). f a -> res)
> -> (forall (f :: Type -> Type) . f res)
> -> res
> f x y = x y
> }}}
>
> How hard would it be to expand that to `(x @Type @f @res) (y @f)` or (x
> @Type @Any @res) (y @Any)
>
> {{{#!hs
> f :: forall res (f :: Type -> Type)
> . (forall k (f :: k -> Type) (a :: k). f a -> res)
> -> (forall (f :: Type -> Type) . f res)
> -> res
> f x y = (x @Type @f @res) (y @f)
> }}}
>
> ----
>
> Other ghci ideas: #15610, #15613
New description:
Example inspired by #40.
ghci already has a
[https://downloads.haskell.org/~ghc/latest/docs/html/users_guide/ghci.html
#ghci-cmd-:type-at :type-at] command for reporting a type in a range
{{{
>> :type-at X.hs 6 6 6 7 f
Int -> Int
}}}
A similar thing (for integrating into IDEs) is doing the same for visible
type applications. An innocent expression like `x y` has a lot going on
under the surface
{{{#!hs
{-# Language RankNTypes #-}
{-# Language PolyKinds #-}
{-# Language KindSignatures #-}
import Data.Kind
f :: forall res
. (forall k (f :: k -> Type) (a :: k). f a -> res)
-> (forall (f :: Type -> Type) . f res)
-> res
f x y = x y
}}}
How hard would it be to expand that to `(x @Type @f @res) (y @f)` (or `(x
@Type @Any @res) (y @Any)`)
{{{#!hs
f :: forall res (f :: Type -> Type)
. (forall k (f :: k -> Type) (a :: k). f a -> res)
-> (forall (f :: Type -> Type) . f res)
-> res
f x y = (x @Type @f @res) (y @f)
}}}
----
Other ghci ideas: #15610, #15613
--
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/15762#comment:1>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list