Forked from
Glasgow Haskell Compiler / GHC
5811 commits behind the upstream repository.
-
This moves all URL references to Trac tickets to their corresponding GitLab counterparts.
This moves all URL references to Trac tickets to their corresponding GitLab counterparts.
Code owners
Assign users and groups as approvers for specific file changes. Learn more.
gadt-fd.hs 622 B
{-# LANGUAGE GADTs #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE UndecidableInstances #-}
-- #345
module ShouldCompile where
data Succ n
data Zero
class Plus x y z | x y -> z
instance Plus Zero x x
instance Plus x y z => Plus (Succ x) y (Succ z)
infixr 5 :::
data List :: * -> * -> * where
Nil :: List a Zero
(:::) :: a -> List a n -> List a (Succ n)
append :: Plus x y z => List a x -> List a y -> List a z
append Nil ys = ys
append (x ::: xs) ys = x ::: append xs ys