module Sifflet.Text.Repr
    (Repr(..)
    , Name(..)
    )

where

import Data.Number.Sifflet
import Data.List (intercalate)

-- | class Repr: representable by a String or a list of Strings
--
-- repr x is a String representation of x.
-- reprl x is a [String] representation of x,
--   where the first element should be the same as repr x,
--   and the rest provide auxiliary information
--   that you want to be shown with x.
-- reprs x is a reduction of reprl x to a single String.
-- reprList prefix infix postfix xs is the representation of a list of xs
--
-- Minimal complete implementation: define repr, or define reprl.
-- The normal way is to define repr.  Define reprl instead,
-- if for some reason you want to include additional information
-- such as the value of an expression in an expression node.
--
-- Examples:
--    -   (3 :: Int) has repr => "3", reprl => ["3"], reprs => "3"
--    -   In Sifflet.Language.Expr, (ENode (NSymbol "x") (EvalOk (3 :: Int)
--        has reprl => ["x", "3"], reprs => "x 3", and repr => "x".
--    -   reprList "(" " " ")" [3 :: Int, 4, 5] => "(3 4 5)"

class Repr a where

  repr :: a -> String
  repr = head . reprl

  reprl :: a -> [String]
  reprl x = [repr x]

  reprs :: a -> String
  reprs = unwords . reprl

  reprList :: String -> String -> String -> [a] -> String
  reprList pre tween post xs =
      pre ++ intercalate tween (map repr xs) ++ post

instance Repr Bool where repr = show
instance Repr Char where repr = show
instance Repr Int where repr = show
instance Repr Integer where repr = show
instance Repr Number where repr = show
instance Repr Float where repr = show
instance Repr Double where repr = show

-- instance Repr String won't work because String is a type synonym,
-- unless you ask ghc nicely, which I'd prefer not to do.
-- Use Name data type in Testing/Tree.hs instead, or Symbol in Expr.hs
-- I don't know if I can use Expr.Symbol here, since Expr.hs also
-- imports Tree.hs (this file) -- is mutual import allowed?

data Name = Name String
          deriving (Eq, Read, Show)

instance Repr Name where
  repr (Name s) = s