This commit is contained in:
Alan Zimmerman 2014-08-23 11:01:49 +02:00
parent 5b32667060
commit 9101f306d1
3 changed files with 77 additions and 0 deletions

28
ISSUE336.md Normal file
View File

@ -0,0 +1,28 @@
https://github.com/kazu-yamamoto/ghc-mod/issues/336
```
{-# LANGUAGE DataKinds, TypeFamilies, TypeOperators, GADTs, KindSignatures #-}
module Vect where
data Nat = Z | S Nat
type family (n :: Nat) :+ (m :: Nat) :: Nat
type instance Z :+ m = m
type instance S n :+ m = S (n :+ m)
data Vect :: Nat -> * -> * where
VNil :: Vect Z a
(:::) :: a -> Vect n a -> Vect (S n) a
vAppend :: Vect n a -> Vect m a -> Vect (n :+ m) a
vAppend x y = _vAppend_body
lAppend :: [a] -> [a] -> [a]
lAppend x y = _lAppend_body
data MyList a = Nil | Cons a (MyList a)
mlAppend :: MyList a -> MyList a -> MyList a
mlAppend x y = _mlAppend_body
```

25
test/CaseSplitSpec.hs Normal file
View File

@ -0,0 +1,25 @@
{-# LANGUAGE CPP #-}
module CaseSplitSpec where
import Control.Applicative ((<$>))
import Data.List (isPrefixOf)
import Language.Haskell.GhcMod
#if __GLASGOW_HASKELL__ < 706
import System.Environment.Executable (getExecutablePath)
#else
import System.Environment (getExecutablePath)
#endif
import System.Exit
import System.FilePath
import System.Process
import Test.Hspec
import TestUtils
import Dir
spec :: Spec
spec = do
describe "case split" $ do
it "does not blow up on HsWithBndrs panic" $ do
withDirectory_ "test/data/case-split" $ do
res <- runD $ splits "Vect.hs" 24 10
res `shouldBe` "9 5 11 40 \"Int -> a -> a -> a\"\n7 1 11 40 \"Int -> Integer\"\n"

View File

@ -0,0 +1,24 @@
{-# LANGUAGE DataKinds, TypeFamilies, TypeOperators, GADTs, KindSignatures #-}
module Vect where
data Nat = Z | S Nat
type family (n :: Nat) :+ (m :: Nat) :: Nat
type instance Z :+ m = m
type instance S n :+ m = S (n :+ m)
data Vect :: Nat -> * -> * where
VNil :: Vect Z a
(:::) :: a -> Vect n a -> Vect (S n) a
vAppend :: Vect n a -> Vect m a -> Vect (n :+ m) a
vAppend x y = _vAppend_body
lAppend :: [a] -> [a] -> [a]
lAppend x y = _lAppend_body
data MyList a = Nil | Cons a (MyList a)
mlAppend :: MyList a -> MyList a -> MyList a
mlAppend x y = _mlAppend_body