[Haskell-cafe] More concise code using phantom types

Nikita Kartashov snailandmail at gmail.com
Fri Aug 7 23:28:57 UTC 2015


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





-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/haskell-cafe/attachments/20150808/26a1b3fc/attachment.html>
-------------- next part --------------
A non-text attachment was scrubbed...
Name: signature.asc
Type: application/pgp-signature
Size: 496 bytes
Desc: Message signed with OpenPGP using GPGMail
URL: <http://mail.haskell.org/pipermail/haskell-cafe/attachments/20150808/26a1b3fc/attachment.sig>


More information about the Haskell-Cafe mailing list