{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE ExplicitForAll #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE GADTs #-}
module Data.Types.Injective where
import qualified Numeric.Natural as N
import Data.Default
import qualified Data.Maybe as M
import qualified Data.Ratio as R
import qualified Data.Sequence as S
import qualified Data.Text as TS
import qualified Data.Text.Encoding as TS
import qualified Data.Text.Lazy as TL
import qualified Data.Text.Lazy.Encoding as TL
import qualified Data.Vector.Generic as VG
import qualified VectorBuilder.Builder as VB
import qualified VectorBuilder.Vector as VB
import qualified Numeric.Peano as PN
class Injective a b where
to :: forall b1 a1. (b1 ~ b, a1 ~ a) => a -> b
instance Injective a a where
to = id
instance Injective TS.Text String where to = TS.unpack
instance Injective String TS.Text where to = TS.pack
instance Injective TS.Text TL.Text where to = TL.fromStrict
instance Injective TL.Text TS.Text where to = TL.toStrict
instance Injective TL.Text String where to = TL.unpack
instance Injective String TL.Text where to = TL.pack
instance Injective PN.Whole Integer where to = PN.fromPeano
instance Injective Integer PN.Whole where to = fromInteger
instance Injective N.Natural PN.Nat where to = fromIntegral
instance Injective PN.Nat N.Natural where to = fromIntegral
instance Default a => Injective (Maybe b) (Either a b) where
to = M.maybe (Left def) Right
instance Injective N.Natural Integer where to = toInteger
instance Injective N.Natural PN.Whole where to = flip PN.Whole PN.Pos . fromIntegral
instance Injective N.Natural R.Rational where to = to . toInteger
instance Injective PN.Nat Integer where to = PN.fromPeano
instance Injective PN.Nat PN.Whole where to = flip PN.Whole PN.Pos
instance Injective PN.Nat R.Rational where to = flip (R.%) 1 . fromIntegral
instance Injective Integer R.Rational where to = flip (R.%) 1
instance Injective PN.Whole R.Rational where
to (PN.Whole n PN.Pos) = (fromIntegral n) R.% 1
to (PN.Whole n PN.Neg) = negate (fromIntegral n) R.% 1
instance VG.Vector v a => Injective (S.Seq a) (v a) where
to = VB.build . VB.foldable
instance VG.Vector v a => Injective (v a) (S.Seq a) where
to v = S.fromFunction (VG.length v) (v VG.!)