Difference between revisions of "Roman numerals"

From HaskellWiki
Jump to navigation Jump to search
(Roman numerals; oneliner and type encoding; first revision)
 
(Category:Mathematics)
Line 81: Line 81:
   
 
[[Category:Idioms]]
 
[[Category:Idioms]]
  +
[[Category:Mathematics]]

Revision as of 14:50, 8 November 2006

The system of Roman numerals is a numeral system originating in ancient Rome, and was adapted from Etruscan numerals. The system used in classical antiquity was slightly modified in the Middle Ages to produce the system we use today. It is based on certain letters which are given values as numerals.

Oneliner

This is a nearly-completely points-freed expression which evaluates a given Roman numeral as a String to the corresponding Int. The folded function is not points-freed for ease of reading, and it would also need an `if' function which needs separate definition.

import Data.Maybe (fromJust)

romanToInt :: String -> Int
romanToInt = fst . foldr (\p (t,s) -> if p >= s then (t+p,p) else (t-p,p)) (0,0) . map (fromJust . flip lookup (zip "IVXLCDM" [1,5,10,50,100,500,1000]))

Roman (type-)numerals

The function `roman' here infers the value of the Roman numeral from the type of its first argument, which in turn is left unevaluated, and returns it as an Int.

{-# OPTIONS_GHC -fglasgow-exts #-}
module Romans where

class Roman t where
  roman :: t -> Int

data O   -- 0
data I a -- 1
data V a -- 5
data X a -- 10
data L a -- 50
data C a -- 100
data D a -- 500
data M a -- 1000

instance                Roman O         where roman _ = 0
instance                Roman (I O)     where roman _ = 1
instance                Roman (V O)     where roman _ = 5
instance                Roman (X O)     where roman _ = 10

instance Roman (I a) => Roman (I (I a)) where roman _ = roman (undefined :: (I a)) + 1
instance Roman a     => Roman (I (V a)) where roman _ = roman (undefined :: a)     + 4
instance Roman a     => Roman (I (X a)) where roman _ = roman (undefined :: a)     + 9

instance Roman (I a) => Roman (V (I a)) where roman _ = roman (undefined :: (I a)) + 5
instance Roman (V a) => Roman (V (V a)) where roman _ = roman (undefined :: (V a)) + 5

instance Roman (I a) => Roman (X (I a)) where roman _ = roman (undefined :: (I a)) + 10
instance Roman (V a) => Roman (X (V a)) where roman _ = roman (undefined :: (V a)) + 10
instance Roman (X a) => Roman (X (X a)) where roman _ = roman (undefined :: (X a)) + 10
instance Roman a     => Roman (X (L a)) where roman _ = roman (undefined :: a)     + 40
instance Roman a     => Roman (X (C a)) where roman _ = roman (undefined :: a)     + 90
instance Roman a     => Roman (X (D a)) where roman _ = roman (undefined :: a)     + 490

instance Roman a     => Roman (L a)     where roman _ = roman (undefined :: a)     + 50

instance Roman (I a) => Roman (C (I a)) where roman _ = roman (undefined :: (I a)) + 100
instance Roman (V a) => Roman (C (V a)) where roman _ = roman (undefined :: (V a)) + 100
instance Roman (X a) => Roman (C (X a)) where roman _ = roman (undefined :: (X a)) + 100
instance Roman (L a) => Roman (C (L a)) where roman _ = roman (undefined :: (L a)) + 100
instance Roman (C a) => Roman (C (C a)) where roman _ = roman (undefined :: (C a)) + 100
instance Roman a     => Roman (C (D a)) where roman _ = roman (undefined :: a)     + 400
instance Roman a     => Roman (C (M a)) where roman _ = roman (undefined :: a)     + 900

instance Roman a     => Roman (D a)     where roman _ = roman (undefined :: a)     + 500

instance Roman a     => Roman (M a)     where roman _ = roman (undefined :: a)     + 1000

-- Example type: XVI ~> X (V (I O)); MCMXCIX ~> M (C (M (X (C (I (X O))))))

powersoftwo = [roman (undefined :: (I (I O))),
               roman (undefined :: (I (V O))),
               roman (undefined :: (V (I (I (I O))))),
               roman (undefined :: (X (V (I O)))),
               roman (undefined :: (X (X (X (I (I O)))))),
               roman (undefined :: (L (X (I (V O))))),
               roman (undefined :: (C (X (X (V (I (I (I O)))))))),
               roman (undefined :: (C (C (L (V (I O)))))),
               roman (undefined :: (D (X (I (I O))))),
               roman (undefined :: (M (X (X (I (V O)))))),
               roman (undefined :: (M (M (X (L (V (I (I (I O)))))))))]