Skip to content
Snippets Groups Projects
Commit 8324f0b7 authored by Bodigrim's avatar Bodigrim Committed by Marge Bot
Browse files

Test proxy-polymorphic sameNat and sameSymbol

parent 4e47217f
No related branches found
No related tags found
No related merge requests found
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE KindSignatures #-}
module Lib where
import Data.Type.Equality
import GHC.TypeLits
import GHC.TypeNats
data A (t :: Nat) = A
data B (t :: Nat) = B
data C (t :: Symbol) = C
data D (t :: Symbol) = D
cmpNats :: (KnownNat n, KnownNat m) => A n -> B m -> Bool
cmpNats a b = case a `sameNat` b of
Nothing -> False
Just Refl -> True
cmpSymbols :: (KnownSymbol n, KnownSymbol m) => C n -> D m -> Bool
cmpSymbols c d = case c `sameSymbol` d of
Nothing -> False
Just Refl -> True
test('T16586', normal, compile_and_run, ['-O2'])
# Event-manager not supported on Windows
test('T16916', when(opsys('mingw32'), skip), compile_and_run, ['-O2 -threaded'])
test('T17310', normal, compile, [''])
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment