{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE Rank2Types #-}
{-# LANGUAGE TypeFamilies #-}
module Toml.Bi.Map
(
BiMap (..)
, TomlBiMap
, invert
, iso
, prism
, TomlBiMapError (..)
, wrongConstructor
, prettyBiMapError
, mkAnyValueBiMap
, _TextBy
, _LTextText
, _NaturalInteger
, _StringText
, _ReadString
, _BoundedInteger
, _ByteStringText
, _LByteStringText
, _Array
, _Bool
, _Double
, _Integer
, _Text
, _LText
, _ZonedTime
, _LocalTime
, _Day
, _TimeOfDay
, _String
, _Read
, _Natural
, _Word
, _Int
, _Float
, _ByteString
, _LByteString
, _Set
, _IntSet
, _HashSet
, _NonEmpty
, _Left
, _Right
, _Just
, toMArray
) where
import Control.Arrow ((>>>))
import Control.Monad ((>=>))
import Control.DeepSeq (NFData)
import Data.Bifunctor (bimap, first)
import Data.ByteString (ByteString)
import Data.Hashable (Hashable)
import Data.Semigroup (Semigroup (..))
import Data.Text (Text)
import Data.Time (Day, LocalTime, TimeOfDay, ZonedTime)
import Data.Word (Word)
import GHC.Generics (Generic)
import Numeric.Natural (Natural)
import Text.Read (readEither)
import Toml.Type (AnyValue (..), MatchError (..), TValue (..), Value (..), applyAsToAny, matchBool,
matchDay, matchDouble, matchHours, matchInteger, matchLocal, matchText,
matchZoned, mkMatchError, toMArray)
import qualified Control.Category as Cat
import qualified Data.ByteString.Lazy as BL
import qualified Data.HashSet as HS
import qualified Data.IntSet as IS
import qualified Data.List.NonEmpty as NE
import qualified Data.Set as S
import qualified Data.Text as T
import qualified Data.Text.Encoding as T
import qualified Data.Text.Lazy as TL
import qualified Data.Text.Lazy.Encoding as TL
data BiMap e a b = BiMap
{ forward :: a -> Either e b
, backward :: b -> Either e a
}
instance Cat.Category (BiMap e) where
id :: BiMap e a a
id = BiMap Right Right
(.) :: BiMap e b c -> BiMap e a b -> BiMap e a c
bc . ab = BiMap
{ forward = forward ab >=> forward bc
, backward = backward bc >=> backward ab
}
invert :: BiMap e a b -> BiMap e b a
invert (BiMap f g) = BiMap g f
iso :: (a -> b) -> (b -> a) -> BiMap e a b
iso f g = BiMap (Right . f) (Right . g)
prism :: (field -> object) -> (object -> Either error field) -> BiMap error object field
prism review preview = BiMap preview (Right . review)
type TomlBiMap = BiMap TomlBiMapError
data TomlBiMapError
= WrongConstructor
Text
Text
| WrongValue
MatchError
| ArbitraryError
Text
deriving (Eq, Show, Generic, NFData)
prettyBiMapError :: TomlBiMapError -> Text
prettyBiMapError = \case
WrongConstructor expected actual -> T.unlines
[ "Invalid constructor"
, " * Expected: " <> expected
, " * Actual: " <> actual
]
WrongValue (MatchError expected actual) -> T.unlines
[ "Invalid constructor"
, " * Expected: " <> tShow expected
, " * Actual: " <> tShow actual
]
ArbitraryError text -> text
wrongConstructor
:: Show a
=> Text
-> a
-> Either TomlBiMapError b
wrongConstructor constructor x = Left $ WrongConstructor constructor (tShow x)
_Left :: (Show l, Show r) => TomlBiMap (Either l r) l
_Left = prism Left $ \case
Left l -> Right l
x -> wrongConstructor "Left" x
_Right :: (Show l, Show r) => TomlBiMap (Either l r) r
_Right = prism Right $ \case
Right r -> Right r
x -> wrongConstructor "Right" x
_Just :: Show r => TomlBiMap (Maybe r) r
_Just = prism Just $ \case
Just r -> Right r
x -> wrongConstructor "Just" x
mkAnyValueBiMap
:: forall a (tag :: TValue) . (forall (t :: TValue) . Value t -> Either MatchError a)
-> (a -> Value tag)
-> TomlBiMap a AnyValue
mkAnyValueBiMap matchValue toValue = BiMap
{ forward = Right . toAnyValue
, backward = fromAnyValue
}
where
toAnyValue :: a -> AnyValue
toAnyValue = AnyValue . toValue
fromAnyValue :: AnyValue -> Either TomlBiMapError a
fromAnyValue (AnyValue value) = first WrongValue $ matchValue value
_TextBy
:: forall a .
(a -> Text)
-> (Text -> Either Text a)
-> TomlBiMap a AnyValue
_TextBy toText parseText = BiMap toAnyValue fromAnyValue
where
toAnyValue :: a -> Either TomlBiMapError AnyValue
toAnyValue = Right . AnyValue . Text . toText
fromAnyValue :: AnyValue -> Either TomlBiMapError a
fromAnyValue (AnyValue v) =
first WrongValue (matchText v) >>= first ArbitraryError . parseText
_Bool :: TomlBiMap Bool AnyValue
_Bool = mkAnyValueBiMap matchBool Bool
_Integer :: TomlBiMap Integer AnyValue
_Integer = mkAnyValueBiMap matchInteger Integer
_Double :: TomlBiMap Double AnyValue
_Double = mkAnyValueBiMap matchDouble Double
_Text :: TomlBiMap Text AnyValue
_Text = mkAnyValueBiMap matchText Text
_LTextText :: BiMap e TL.Text Text
_LTextText = iso TL.toStrict TL.fromStrict
_LText :: TomlBiMap TL.Text AnyValue
_LText = _LTextText >>> _Text
_ZonedTime :: TomlBiMap ZonedTime AnyValue
_ZonedTime = mkAnyValueBiMap matchZoned Zoned
_LocalTime :: TomlBiMap LocalTime AnyValue
_LocalTime = mkAnyValueBiMap matchLocal Local
_Day :: TomlBiMap Day AnyValue
_Day = mkAnyValueBiMap matchDay Day
_TimeOfDay :: TomlBiMap TimeOfDay AnyValue
_TimeOfDay = mkAnyValueBiMap matchHours Hours
_StringText :: BiMap e String Text
_StringText = iso T.pack T.unpack
_String :: TomlBiMap String AnyValue
_String = _StringText >>> _Text
_ReadString :: (Show a, Read a) => TomlBiMap a String
_ReadString = BiMap (Right . show) (first (ArbitraryError . T.pack) . readEither)
_Read :: (Show a, Read a) => TomlBiMap a AnyValue
_Read = _ReadString >>> _String
_NaturalInteger :: TomlBiMap Natural Integer
_NaturalInteger = BiMap (Right . toInteger) eitherInteger
where
eitherInteger :: Integer -> Either TomlBiMapError Natural
eitherInteger n
| n < 0 = Left $ ArbitraryError $ "Value is below zero, but expected Natural: " <> tShow n
| otherwise = Right (fromIntegral n)
_Natural :: TomlBiMap Natural AnyValue
_Natural = _NaturalInteger >>> _Integer
_BoundedInteger :: (Integral a, Bounded a, Show a) => TomlBiMap a Integer
_BoundedInteger = BiMap (Right . toInteger) eitherBounded
where
eitherBounded :: forall a. (Integral a, Bounded a, Show a) => Integer -> Either TomlBiMapError a
eitherBounded n
| n < toInteger (minBound @a) =
let msg = "Value " <> tShow n <> " is less than minBound: " <> tShow (minBound @a)
in Left $ ArbitraryError msg
| n > toInteger (maxBound @a) =
let msg = "Value " <> tShow n <> " is greater than maxBound: " <> tShow (maxBound @a)
in Left $ ArbitraryError msg
| otherwise = Right (fromIntegral n)
_Word :: TomlBiMap Word AnyValue
_Word = _BoundedInteger >>> _Integer
_Int :: TomlBiMap Int AnyValue
_Int = _BoundedInteger >>> _Integer
_Float :: TomlBiMap Float AnyValue
_Float = iso realToFrac realToFrac >>> _Double
_ByteStringText :: TomlBiMap ByteString Text
_ByteStringText = prism T.encodeUtf8 eitherText
where
eitherText :: ByteString -> Either TomlBiMapError Text
eitherText = either (\err -> Left $ ArbitraryError $ tShow err) Right . T.decodeUtf8'
_ByteString :: TomlBiMap ByteString AnyValue
_ByteString = _ByteStringText >>> _Text
_LByteStringText :: TomlBiMap BL.ByteString Text
_LByteStringText = prism (TL.encodeUtf8 . TL.fromStrict) eitherText
where
eitherText :: BL.ByteString -> Either TomlBiMapError Text
eitherText = bimap (ArbitraryError . tShow) TL.toStrict . TL.decodeUtf8'
_LByteString :: TomlBiMap BL.ByteString AnyValue
_LByteString = _LByteStringText >>> _Text
_Array :: forall a . TomlBiMap a AnyValue -> TomlBiMap [a] AnyValue
_Array elementBimap = BiMap toAnyValue fromAnyValue
where
toAnyValue :: [a] -> Either TomlBiMapError AnyValue
toAnyValue = mapM (forward elementBimap) >=> bimap WrongValue AnyValue . toMArray
fromAnyValue :: AnyValue -> Either TomlBiMapError [a]
fromAnyValue (AnyValue v) = matchElements (backward elementBimap) v
matchElements :: (AnyValue -> Either TomlBiMapError a) -> Value t -> Either TomlBiMapError [a]
matchElements match (Array a) = mapM (applyAsToAny match) a
matchElements _ val = first WrongValue $ mkMatchError TArray val
_NonEmpty :: TomlBiMap a AnyValue -> TomlBiMap (NE.NonEmpty a) AnyValue
_NonEmpty bi = _NonEmptyArray >>> _Array bi
_NonEmptyArray :: TomlBiMap (NE.NonEmpty a) [a]
_NonEmptyArray = BiMap
{ forward = Right . NE.toList
, backward = maybe (Left $ ArbitraryError "Empty array list, but expected NonEmpty") Right . NE.nonEmpty
}
_Set :: (Ord a) => TomlBiMap a AnyValue -> TomlBiMap (S.Set a) AnyValue
_Set bi = iso S.toList S.fromList >>> _Array bi
_HashSet :: (Eq a, Hashable a) => TomlBiMap a AnyValue -> TomlBiMap (HS.HashSet a) AnyValue
_HashSet bi = iso HS.toList HS.fromList >>> _Array bi
_IntSet :: TomlBiMap IS.IntSet AnyValue
_IntSet = iso IS.toList IS.fromList >>> _Array _Int
tShow :: Show a => a -> Text
tShow = T.pack . show