{-# LANGUAGE DataKinds #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE RoleAnnotations #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE UndecidableInstances #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
module Data.UnitsOfMeasure.Show
( showQuantity
, showUnit
) where
import Data.UnitsOfMeasure.Internal
import Data.UnitsOfMeasure.Singleton
import Data.List (group)
instance (Show a, KnownUnit (Unpack u)) => Show (Quantity a u) where
show x = "[u| " ++ showQuantity x ++ " |]"
showQuantity :: forall a u. (Show a, KnownUnit (Unpack u)) => Quantity a u -> String
showQuantity (MkQuantity x) = show x ++ if s == "1" then "" else ' ':s
where s = showUnit (undefined :: proxy u)
showUnit :: forall proxy u . KnownUnit (Unpack u) => proxy u -> String
showUnit _ = showUnitBits (unitVal (undefined :: proxy' (Unpack u)))
showUnitBits :: UnitSyntax String -> String
showUnitBits ([] :/ []) = "1"
showUnitBits (xs :/ []) = showPos xs
showUnitBits ([] :/ ys) = showNeg ys
showUnitBits (xs :/ ys) = showPos xs ++ " / " ++ showPos ys
showPos :: [String] -> String
showPos = unwords . map (\ xs -> showAtom (head xs, length xs)) . group
showNeg :: [String] -> String
showNeg = unwords . map (\ xs -> showAtom (head xs, negate $ length xs)) . group
showAtom :: (String, Int) -> String
showAtom (s, 1) = s
showAtom (s, i) = s ++ "^" ++ show i