{-# LANGUAGE TypeSynonymInstances #-}
{-# LANGUAGE FlexibleInstances #-}

{- |
Type class for textual data and simple (fromItegral like) conversion
between them.

The conversion utility here, although simple may not be the fastest one
available, and aims at preserving the textual representation of data,
not its binary structure. This, given the existence of codecs with
ambiguous representation means that the following function may evaluate
to False:

mayBeFalse :: Textual a => a -> Bool
mayBeFalse a = let
    b = fromText a
    in a == b

-}
module Data.Textual.Class where

import Data.String
import qualified Data.ByteString as SB
import qualified Data.ByteString.Lazy as LB
import qualified Codec.Binary.UTF8.String as UTF8
import qualified Data.Text as ST
import qualified Data.Text.Lazy as LT

{- | Type class for data structures that are logically text -}
class IsString a => Textual a where
  toString :: a -> String

instance Textual String where
  toString = id
{- | With UTF-8 encoding -}
instance Textual SB.ByteString where
  toString = UTF8.decode . SB.unpack
{- | With UTF-8 encoding -}
instance Textual LB.ByteString where
  toString = UTF8.decode . LB.unpack
instance Textual ST.Text where
  toString = ST.unpack

{- | Converts between instances of Textual -}
fromTextual :: (Textual a, Textual b) => a -> b
fromTextual = fromString . toString