summaryrefslogtreecommitdiff
path: root/testsuite/tests/typecheck/should_compile/T14185.hs
blob: 41e47d2913297c59766ef795a028fc52444e59a2 (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
{-# LANGUAGE MagicHash, UnboxedTuples, MultiParamTypeClasses, TypeFamilies,
  FunctionalDependencies, KindSignatures, PolyKinds, DataKinds,
  UndecidableInstances #-}
module T14185 where

import GHC.Types
import GHC.Prim


class Unbox (t :: *) (r :: TYPE k) | t -> r, r -> t where
  unbox :: t -> r
  box :: r -> t

instance Unbox Int Int# where
  unbox (I# i) = i
  box i = I# i

instance Unbox Char Char# where
  unbox (C# c) = c
  box c = C# c

instance (Unbox a a', Unbox b b') => Unbox (a,b) (# a', b' #) where
  unbox (a,b) = (# unbox a, unbox b #)
  box (# a, b #) = (box a, box b)

testInt :: Int
testInt = box (unbox 1)

testTup :: (Int, Char)
testTup = box (unbox (1, 'a'))