Skip to content

Commit 55293bd

Browse files
konnpepeiborra
authored andcommitted
Adds :kind and :kind! commands to Eval Plugin (haskell#345)
* Implements `:kind!` GHCi command to Eval plugin * Adds golden tests for `:kind!` * Removes redundant lines * Adds `:kind` command that returns kind only without normalisation * Test cases for `:kind` * Fixes `Applies file LANGUAGE extensions` to avoid sufferring from ImportLens * Removes redundant leading space
1 parent f0c2439 commit 55293bd

File tree

12 files changed

+80
-3
lines changed

12 files changed

+80
-3
lines changed

src/Ide/Plugin/Eval.hs

Lines changed: 15 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -63,7 +63,7 @@ import GHC (DynFlags, ExecResult (..), Gene
6363
setInteractiveDynFlags,
6464
setLogAction,
6565
setSessionDynFlags, setTargets,
66-
simpleImportDecl, ways)
66+
simpleImportDecl, typeKind, ways)
6767
import GHC.Generics (Generic)
6868
import GhcMonad (modifySession)
6969
import GhcPlugins (defaultLogActionHPutStrDoc,
@@ -86,6 +86,8 @@ import qualified Control.Exception as E
8686
import Control.DeepSeq ( NFData
8787
, deepseq
8888
)
89+
import Outputable (Outputable(ppr), showSDoc)
90+
import Control.Applicative ((<|>))
8991

9092
descriptor :: PluginId -> PluginDescriptor
9193
descriptor plId =
@@ -245,6 +247,18 @@ done, we want to switch back to GhcSessionDeps:
245247

246248
df <- liftIO $ evalGhcEnv hscEnv' getSessionDynFlags
247249
let eval (stmt, l)
250+
| let stmt0 = T.strip $ T.pack stmt -- For stripping and de-prefixing
251+
, Just (reduce, type_) <-
252+
(True,) <$> T.stripPrefix ":kind! " stmt0
253+
<|> (False,) <$> T.stripPrefix ":kind " stmt0
254+
= do
255+
let input = T.strip type_
256+
(ty, kind) <- typeKind reduce $ T.unpack input
257+
pure $ Just
258+
$ T.unlines
259+
$ map ("-- " <>)
260+
$ (input <> " :: " <> T.pack (showSDoc df $ ppr kind))
261+
: [ "= " <> T.pack (showSDoc df $ ppr ty) | reduce]
248262
| isStmt df stmt = do
249263
-- set up a custom interactive print function
250264
liftIO $ writeFile temp ""

test/functional/Eval.hs

Lines changed: 6 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -64,6 +64,12 @@ tests = testGroup
6464
, testCase "Refresh a multiline evaluation" $ goldenTest "T7.hs"
6565
, testCase "Evaluate incorrect expressions" $ goldenTest "T8.hs"
6666
, testCase "Applies file LANGUAGE extensions" $ goldenTest "T9.hs"
67+
, testCase "Evaluate a type with :kind!" $ goldenTest "T10.hs"
68+
, testCase "Reports an error for an incorrect type with :kind!"
69+
$ goldenTest "T11.hs"
70+
, testCase "Shows a kind with :kind" $ goldenTest "T12.hs"
71+
, testCase "Reports an error for an incorrect type with :kind"
72+
$ goldenTest "T13.hs"
6773
]
6874

6975
goldenTest :: FilePath -> IO ()

test/testdata/eval/T10.hs

Lines changed: 9 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,9 @@
1+
{-# LANGUAGE DataKinds, TypeOperators #-}
2+
module T10 where
3+
import GHC.TypeNats ( type (+) )
4+
5+
type Dummy = 1 + 1
6+
7+
-- >>> type N = 1
8+
-- >>> type M = 40
9+
-- >>> :kind! N + M + 1

test/testdata/eval/T10.hs.expected

Lines changed: 11 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,11 @@
1+
{-# LANGUAGE DataKinds, TypeOperators #-}
2+
module T10 where
3+
import GHC.TypeNats ( type (+) )
4+
5+
type Dummy = 1 + 1
6+
7+
-- >>> type N = 1
8+
-- >>> type M = 40
9+
-- >>> :kind! N + M + 1
10+
-- N + M + 1 :: Nat
11+
-- = 42

test/testdata/eval/T11.hs

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,3 @@
1+
module T11 where
2+
3+
-- >>> :kind! a

test/testdata/eval/T11.hs.expected

Lines changed: 4 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,4 @@
1+
module T11 where
2+
3+
-- >>> :kind! a
4+
-- Not in scope: type variable ‘a’

test/testdata/eval/T12.hs

Lines changed: 9 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,9 @@
1+
{-# LANGUAGE DataKinds, TypeOperators #-}
2+
module T12 where
3+
import GHC.TypeNats ( type (+) )
4+
5+
type Dummy = 1 + 1
6+
7+
-- >>> type N = 1
8+
-- >>> type M = 40
9+
-- >>> :kind N + M + 1

test/testdata/eval/T12.hs.expected

Lines changed: 10 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,10 @@
1+
{-# LANGUAGE DataKinds, TypeOperators #-}
2+
module T12 where
3+
import GHC.TypeNats ( type (+) )
4+
5+
type Dummy = 1 + 1
6+
7+
-- >>> type N = 1
8+
-- >>> type M = 40
9+
-- >>> :kind N + M + 1
10+
-- N + M + 1 :: Nat

test/testdata/eval/T13.hs

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,3 @@
1+
module T13 where
2+
3+
-- >>> :kind a

test/testdata/eval/T13.hs.expected

Lines changed: 4 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,4 @@
1+
module T13 where
2+
3+
-- >>> :kind a
4+
-- Not in scope: type variable ‘a’

test/testdata/eval/T9.hs

Lines changed: 3 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,7 @@
11
{-# LANGUAGE DataKinds #-}
22
module T9 where
3-
import Data.Proxy
3+
import Data.Proxy (Proxy(..))
4+
5+
type P = Proxy
46

57
-- >>> Proxy :: Proxy 3

test/testdata/eval/T9.hs.expected

Lines changed: 3 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,8 @@
11
{-# LANGUAGE DataKinds #-}
22
module T9 where
3-
import Data.Proxy
3+
import Data.Proxy (Proxy(..))
4+
5+
type P = Proxy
46

57
-- >>> Proxy :: Proxy 3
68
-- Proxy

0 commit comments

Comments
 (0)