
Hello! Consider the following code: module Units where data Units a = U Double deriving Eq units :: Double -> a -> Units a units value _ = U value data Meters data Yards meters = undefined :: Meters yards = undefined :: Yards instance Show Meters where show _ = "meters" instance Show Yards where show _ = "yards" extractA :: Units a -> a extractA = undefined instance Show a => Show (Units a) where show u@(U value) = show value ++ " " ++ show $ extractA u main = (print $ units 5 yards) >> (print $ units 5 meters) Is it possible to use something instead extractA function here? For example, substitute "extractA u” with “undefined :: a”? GHC disallows it, so is there a way to explain that I only need a token with type a? Also, with highlighting on lpaste: http://lpaste.net/138219. With regards, Nikita Kartashov

On Fri, Aug 7, 2015 at 7:28 PM, Nikita Kartashov
Is it possible to use something instead extractA function here? For example, substitute "extractA u” with “undefined :: a”? GHC disallows it, so is there a way to explain that I only need a token with type a?
It needs a function type there. That said, `const undefined' might work, or even just `undefined', if it can infer the type correctly. I don't *think* you can use 'a' as a type there meaningfully; IIRC it doesn't scope over the method definition, so `a' would be referring to a new type, not the one in the instance header. The ScopedTypeVariables extension would help, along with InstanceSigs so you can specify a signature for `show` with a `forall' in it to activate the scope. See the example at https://downloads.haskell.org/~ghc/latest/docs/html/users_guide/type-class-e... for how to do it. -- brandon s allbery kf8nh sine nomine associates allbery.b@gmail.com ballbery@sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net
participants (2)
-
Brandon Allbery
-
Nikita Kartashov