module Type.Ord (module Type.Ord.Base) where
import Type.Digits (digit, radix, digitTypes)
import Type.Digits.Stage0 (Digit(DigitStop))
import Type.Ord.Base
import Language.Haskell.TH
type instance Compare 'DigitStop 'DigitStop = 'EQ
fmap concat $ sequence [ do
  let dL = return pureTy
      [l, r] = map (varT . mkName) ["l", "r"]
      f x y z = tySynInstD ''Compare [x, y] z
  d <- f [t| $dL $l |] [t| $dL $r |] [t| Compare $l $r |]
  ((d:) . concat) `fmap` sequence [
    let dR = promotedT $ digit m in
    sequence [f [t| $dL $l |] [t| $dR $r |] [t| 'LT |],
              f [t| $dR $l |] [t| $dL $r |] [t| 'GT |]]
    | m <- [n + 1..radix  1] ]
  | (n, pureTy) <- zip [0..] digitTypes ]