{-# LANGUAGE CPP #-}
{-# LANGUAGE GADTs #-}
module Toml.Codec.BiMap.Conversion
(
_Bool
, _Int
, _Word
, _Word8
, _Integer
, _Natural
, _Double
, _Float
, _Text
, _LText
, _ByteString
, _LByteString
, _String
, _ZonedTime
, _LocalTime
, _Day
, _TimeOfDay
, _Array
, _NonEmpty
, _Set
, _HashSet
, _IntSet
, _ByteStringArray
, _LByteStringArray
, _Coerce
, _EnumBounded
, _Read
, _TextBy
, _Validate
, _Hardcoded
, _KeyText
, _KeyString
, _KeyInt
, _Just
, _Left
, _Right
, _LTextText
, _NaturalInteger
, _NonEmptyList
, _StringText
, _ReadString
, _BoundedInteger
, _EnumBoundedText
, _ByteStringText
, _LByteStringText
) where
import Control.Category ((>>>))
import Control.Monad ((>=>))
import Data.Bifunctor (bimap, first)
import Data.ByteString (ByteString)
import Data.Coerce (Coercible, coerce)
import Data.Hashable (Hashable)
import Data.Map (Map)
import Data.Text (Text)
import Data.Time (Day, LocalTime, TimeOfDay, ZonedTime)
import Data.Word (Word8)
import Numeric.Natural (Natural)
import Text.Read (readEither)
import Toml.Codec.BiMap (BiMap (..), TomlBiMap, TomlBiMapError (..), iso, mkAnyValueBiMap, prism,
tShow, wrongConstructor)
import Toml.Parser (TomlParseError (..), parseKey)
import Toml.Type.AnyValue (AnyValue (..), applyAsToAny, matchBool, matchDay, matchDouble,
matchHours, matchInteger, matchLocal, matchText, matchZoned,
mkMatchError, toMArray)
import Toml.Type.Key (Key (..))
import Toml.Type.Printer (prettyKey)
import Toml.Type.Value (TValue (..), Value (..))
import qualified Data.ByteString as BS
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.Map as M
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
_Bool :: TomlBiMap Bool AnyValue
_Bool :: TomlBiMap Bool AnyValue
_Bool = (forall (t :: TValue). Value t -> Either MatchError Bool)
-> (Bool -> Value 'TBool) -> TomlBiMap Bool AnyValue
forall a (tag :: TValue).
(forall (t :: TValue). Value t -> Either MatchError a)
-> (a -> Value tag) -> TomlBiMap a AnyValue
mkAnyValueBiMap Value t -> Either MatchError Bool
forall (t :: TValue). Value t -> Either MatchError Bool
matchBool Bool -> Value 'TBool
Bool
{-# INLINE _Bool #-}
_Integer :: TomlBiMap Integer AnyValue
_Integer :: TomlBiMap Integer AnyValue
_Integer = (forall (t :: TValue). Value t -> Either MatchError Integer)
-> (Integer -> Value 'TInteger) -> TomlBiMap Integer AnyValue
forall a (tag :: TValue).
(forall (t :: TValue). Value t -> Either MatchError a)
-> (a -> Value tag) -> TomlBiMap a AnyValue
mkAnyValueBiMap Value t -> Either MatchError Integer
forall (t :: TValue). Value t -> Either MatchError Integer
matchInteger Integer -> Value 'TInteger
Integer
{-# INLINE _Integer #-}
_Double :: TomlBiMap Double AnyValue
_Double :: TomlBiMap Double AnyValue
_Double = (forall (t :: TValue). Value t -> Either MatchError Double)
-> (Double -> Value 'TDouble) -> TomlBiMap Double AnyValue
forall a (tag :: TValue).
(forall (t :: TValue). Value t -> Either MatchError a)
-> (a -> Value tag) -> TomlBiMap a AnyValue
mkAnyValueBiMap Value t -> Either MatchError Double
forall (t :: TValue). Value t -> Either MatchError Double
matchDouble Double -> Value 'TDouble
Double
{-# INLINE _Double #-}
_Text :: TomlBiMap Text AnyValue
_Text :: TomlBiMap Text AnyValue
_Text = (forall (t :: TValue). Value t -> Either MatchError Text)
-> (Text -> Value 'TText) -> TomlBiMap Text AnyValue
forall a (tag :: TValue).
(forall (t :: TValue). Value t -> Either MatchError a)
-> (a -> Value tag) -> TomlBiMap a AnyValue
mkAnyValueBiMap Value t -> Either MatchError Text
forall (t :: TValue). Value t -> Either MatchError Text
matchText Text -> Value 'TText
Text
{-# INLINE _Text #-}
_LTextText :: BiMap e TL.Text Text
_LTextText :: forall e. BiMap e Text Text
_LTextText = (Text -> Text) -> (Text -> Text) -> BiMap e Text Text
forall a b e. (a -> b) -> (b -> a) -> BiMap e a b
iso Text -> Text
TL.toStrict Text -> Text
TL.fromStrict
{-# INLINE _LTextText #-}
_LText :: TomlBiMap TL.Text AnyValue
_LText :: TomlBiMap Text AnyValue
_LText = BiMap TomlBiMapError Text Text
forall e. BiMap e Text Text
_LTextText BiMap TomlBiMapError Text Text
-> TomlBiMap Text AnyValue -> TomlBiMap Text AnyValue
forall {k} (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> TomlBiMap Text AnyValue
_Text
{-# INLINE _LText #-}
_ZonedTime :: TomlBiMap ZonedTime AnyValue
_ZonedTime :: TomlBiMap ZonedTime AnyValue
_ZonedTime = (forall (t :: TValue). Value t -> Either MatchError ZonedTime)
-> (ZonedTime -> Value 'TZoned) -> TomlBiMap ZonedTime AnyValue
forall a (tag :: TValue).
(forall (t :: TValue). Value t -> Either MatchError a)
-> (a -> Value tag) -> TomlBiMap a AnyValue
mkAnyValueBiMap Value t -> Either MatchError ZonedTime
forall (t :: TValue). Value t -> Either MatchError ZonedTime
matchZoned ZonedTime -> Value 'TZoned
Zoned
{-# INLINE _ZonedTime #-}
_LocalTime :: TomlBiMap LocalTime AnyValue
_LocalTime :: TomlBiMap LocalTime AnyValue
_LocalTime = (forall (t :: TValue). Value t -> Either MatchError LocalTime)
-> (LocalTime -> Value 'TLocal) -> TomlBiMap LocalTime AnyValue
forall a (tag :: TValue).
(forall (t :: TValue). Value t -> Either MatchError a)
-> (a -> Value tag) -> TomlBiMap a AnyValue
mkAnyValueBiMap Value t -> Either MatchError LocalTime
forall (t :: TValue). Value t -> Either MatchError LocalTime
matchLocal LocalTime -> Value 'TLocal
Local
{-# INLINE _LocalTime #-}
_Day :: TomlBiMap Day AnyValue
_Day :: TomlBiMap Day AnyValue
_Day = (forall (t :: TValue). Value t -> Either MatchError Day)
-> (Day -> Value 'TDay) -> TomlBiMap Day AnyValue
forall a (tag :: TValue).
(forall (t :: TValue). Value t -> Either MatchError a)
-> (a -> Value tag) -> TomlBiMap a AnyValue
mkAnyValueBiMap Value t -> Either MatchError Day
forall (t :: TValue). Value t -> Either MatchError Day
matchDay Day -> Value 'TDay
Day
{-# INLINE _Day #-}
_TimeOfDay :: TomlBiMap TimeOfDay AnyValue
_TimeOfDay :: TomlBiMap TimeOfDay AnyValue
_TimeOfDay = (forall (t :: TValue). Value t -> Either MatchError TimeOfDay)
-> (TimeOfDay -> Value 'THours) -> TomlBiMap TimeOfDay AnyValue
forall a (tag :: TValue).
(forall (t :: TValue). Value t -> Either MatchError a)
-> (a -> Value tag) -> TomlBiMap a AnyValue
mkAnyValueBiMap Value t -> Either MatchError TimeOfDay
forall (t :: TValue). Value t -> Either MatchError TimeOfDay
matchHours TimeOfDay -> Value 'THours
Hours
{-# INLINE _TimeOfDay #-}
_StringText :: BiMap e String Text
_StringText :: forall e. BiMap e String Text
_StringText = (String -> Text) -> (Text -> String) -> BiMap e String Text
forall a b e. (a -> b) -> (b -> a) -> BiMap e a b
iso String -> Text
T.pack Text -> String
T.unpack
{-# INLINE _StringText #-}
_String :: TomlBiMap String AnyValue
_String :: TomlBiMap String AnyValue
_String = BiMap TomlBiMapError String Text
forall e. BiMap e String Text
_StringText BiMap TomlBiMapError String Text
-> TomlBiMap Text AnyValue -> TomlBiMap String AnyValue
forall {k} (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> TomlBiMap Text AnyValue
_Text
{-# INLINE _String #-}
_NaturalInteger :: TomlBiMap Natural Integer
_NaturalInteger :: TomlBiMap Natural Integer
_NaturalInteger = (Natural -> Either TomlBiMapError Integer)
-> (Integer -> Either TomlBiMapError Natural)
-> TomlBiMap Natural Integer
forall e a b. (a -> Either e b) -> (b -> Either e a) -> BiMap e a b
BiMap (Integer -> Either TomlBiMapError Integer
forall a b. b -> Either a b
Right (Integer -> Either TomlBiMapError Integer)
-> (Natural -> Integer) -> Natural -> Either TomlBiMapError Integer
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Natural -> Integer
forall a. Integral a => a -> Integer
toInteger) Integer -> Either TomlBiMapError Natural
eitherInteger
where
eitherInteger :: Integer -> Either TomlBiMapError Natural
eitherInteger :: Integer -> Either TomlBiMapError Natural
eitherInteger Integer
n
| Integer
n Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
< Integer
0 = TomlBiMapError -> Either TomlBiMapError Natural
forall a b. a -> Either a b
Left (TomlBiMapError -> Either TomlBiMapError Natural)
-> TomlBiMapError -> Either TomlBiMapError Natural
forall a b. (a -> b) -> a -> b
$ Text -> TomlBiMapError
ArbitraryError (Text -> TomlBiMapError) -> Text -> TomlBiMapError
forall a b. (a -> b) -> a -> b
$ Text
"Value is below zero, but expected Natural: " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Integer -> Text
forall a. Show a => a -> Text
tShow Integer
n
| Bool
otherwise = Natural -> Either TomlBiMapError Natural
forall a b. b -> Either a b
Right (Integer -> Natural
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
n)
_Natural :: TomlBiMap Natural AnyValue
_Natural :: TomlBiMap Natural AnyValue
_Natural = TomlBiMap Natural Integer
_NaturalInteger TomlBiMap Natural Integer
-> TomlBiMap Integer AnyValue -> TomlBiMap Natural AnyValue
forall {k} (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> TomlBiMap Integer AnyValue
_Integer
{-# INLINE _Natural #-}
_BoundedInteger :: (Integral a, Bounded a, Show a) => TomlBiMap a Integer
_BoundedInteger :: forall a. (Integral a, Bounded a, Show a) => TomlBiMap a Integer
_BoundedInteger = (a -> Either TomlBiMapError Integer)
-> (Integer -> Either TomlBiMapError a)
-> BiMap TomlBiMapError a Integer
forall e a b. (a -> Either e b) -> (b -> Either e a) -> BiMap e a b
BiMap (Integer -> Either TomlBiMapError Integer
forall a b. b -> Either a b
Right (Integer -> Either TomlBiMapError Integer)
-> (a -> Integer) -> a -> Either TomlBiMapError Integer
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Integer
forall a. Integral a => a -> Integer
toInteger) Integer -> Either TomlBiMapError a
forall a.
(Integral a, Bounded a, Show a) =>
Integer -> Either TomlBiMapError a
eitherBounded
where
eitherBounded :: forall a. (Integral a, Bounded a, Show a) => Integer -> Either TomlBiMapError a
eitherBounded :: forall a.
(Integral a, Bounded a, Show a) =>
Integer -> Either TomlBiMapError a
eitherBounded Integer
n
| Integer
n Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
< a -> Integer
forall a. Integral a => a -> Integer
toInteger (forall a. Bounded a => a
minBound @a) =
let msg :: Text
msg = Text
"Value " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Integer -> Text
forall a. Show a => a -> Text
tShow Integer
n Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" is less than minBound: " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> a -> Text
forall a. Show a => a -> Text
tShow (forall a. Bounded a => a
minBound @a)
in TomlBiMapError -> Either TomlBiMapError a
forall a b. a -> Either a b
Left (TomlBiMapError -> Either TomlBiMapError a)
-> TomlBiMapError -> Either TomlBiMapError a
forall a b. (a -> b) -> a -> b
$ Text -> TomlBiMapError
ArbitraryError Text
msg
| Integer
n Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
> a -> Integer
forall a. Integral a => a -> Integer
toInteger (forall a. Bounded a => a
maxBound @a) =
let msg :: Text
msg = Text
"Value " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Integer -> Text
forall a. Show a => a -> Text
tShow Integer
n Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" is greater than maxBound: " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> a -> Text
forall a. Show a => a -> Text
tShow (forall a. Bounded a => a
maxBound @a)
in TomlBiMapError -> Either TomlBiMapError a
forall a b. a -> Either a b
Left (TomlBiMapError -> Either TomlBiMapError a)
-> TomlBiMapError -> Either TomlBiMapError a
forall a b. (a -> b) -> a -> b
$ Text -> TomlBiMapError
ArbitraryError Text
msg
| Bool
otherwise = a -> Either TomlBiMapError a
forall a b. b -> Either a b
Right (Integer -> a
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
n)
_Word :: TomlBiMap Word AnyValue
_Word :: TomlBiMap Word AnyValue
_Word = TomlBiMap Word Integer
forall a. (Integral a, Bounded a, Show a) => TomlBiMap a Integer
_BoundedInteger TomlBiMap Word Integer
-> TomlBiMap Integer AnyValue -> TomlBiMap Word AnyValue
forall {k} (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> TomlBiMap Integer AnyValue
_Integer
{-# INLINE _Word #-}
_Word8 :: TomlBiMap Word8 AnyValue
_Word8 :: TomlBiMap Word8 AnyValue
_Word8 = TomlBiMap Word8 Integer
forall a. (Integral a, Bounded a, Show a) => TomlBiMap a Integer
_BoundedInteger TomlBiMap Word8 Integer
-> TomlBiMap Integer AnyValue -> TomlBiMap Word8 AnyValue
forall {k} (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> TomlBiMap Integer AnyValue
_Integer
{-# INLINE _Word8 #-}
_Int :: TomlBiMap Int AnyValue
_Int :: TomlBiMap Int AnyValue
_Int = TomlBiMap Int Integer
forall a. (Integral a, Bounded a, Show a) => TomlBiMap a Integer
_BoundedInteger TomlBiMap Int Integer
-> TomlBiMap Integer AnyValue -> TomlBiMap Int AnyValue
forall {k} (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> TomlBiMap Integer AnyValue
_Integer
{-# INLINE _Int #-}
_Float :: TomlBiMap Float AnyValue
_Float :: TomlBiMap Float AnyValue
_Float = (Float -> Double)
-> (Double -> Float) -> BiMap TomlBiMapError Float Double
forall a b e. (a -> b) -> (b -> a) -> BiMap e a b
iso Float -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double -> Float
forall a b. (Real a, Fractional b) => a -> b
realToFrac BiMap TomlBiMapError Float Double
-> TomlBiMap Double AnyValue -> TomlBiMap Float AnyValue
forall {k} (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> TomlBiMap Double AnyValue
_Double
{-# INLINE _Float #-}
_ByteStringText :: TomlBiMap ByteString Text
_ByteStringText :: TomlBiMap ByteString Text
_ByteStringText = (Text -> ByteString)
-> (ByteString -> Either TomlBiMapError Text)
-> TomlBiMap ByteString Text
forall field object error.
(field -> object)
-> (object -> Either error field) -> BiMap error object field
prism Text -> ByteString
T.encodeUtf8 ByteString -> Either TomlBiMapError Text
eitherText
where
eitherText :: ByteString -> Either TomlBiMapError Text
eitherText :: ByteString -> Either TomlBiMapError Text
eitherText = (UnicodeException -> Either TomlBiMapError Text)
-> (Text -> Either TomlBiMapError Text)
-> Either UnicodeException Text
-> Either TomlBiMapError Text
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (\UnicodeException
err -> TomlBiMapError -> Either TomlBiMapError Text
forall a b. a -> Either a b
Left (TomlBiMapError -> Either TomlBiMapError Text)
-> TomlBiMapError -> Either TomlBiMapError Text
forall a b. (a -> b) -> a -> b
$ Text -> TomlBiMapError
ArbitraryError (Text -> TomlBiMapError) -> Text -> TomlBiMapError
forall a b. (a -> b) -> a -> b
$ UnicodeException -> Text
forall a. Show a => a -> Text
tShow UnicodeException
err) Text -> Either TomlBiMapError Text
forall a b. b -> Either a b
Right (Either UnicodeException Text -> Either TomlBiMapError Text)
-> (ByteString -> Either UnicodeException Text)
-> ByteString
-> Either TomlBiMapError Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Either UnicodeException Text
T.decodeUtf8'
{-# INLINE _ByteStringText #-}
_ByteString :: TomlBiMap ByteString AnyValue
_ByteString :: TomlBiMap ByteString AnyValue
_ByteString = TomlBiMap ByteString Text
_ByteStringText TomlBiMap ByteString Text
-> TomlBiMap Text AnyValue -> TomlBiMap ByteString AnyValue
forall {k} (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> TomlBiMap Text AnyValue
_Text
{-# INLINE _ByteString #-}
_LByteStringText :: TomlBiMap BL.ByteString Text
_LByteStringText :: TomlBiMap ByteString Text
_LByteStringText = (Text -> ByteString)
-> (ByteString -> Either TomlBiMapError Text)
-> TomlBiMap ByteString Text
forall field object error.
(field -> object)
-> (object -> Either error field) -> BiMap error object field
prism (Text -> ByteString
TL.encodeUtf8 (Text -> ByteString) -> (Text -> Text) -> Text -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
TL.fromStrict) ByteString -> Either TomlBiMapError Text
eitherText
where
eitherText :: BL.ByteString -> Either TomlBiMapError Text
eitherText :: ByteString -> Either TomlBiMapError Text
eitherText = (UnicodeException -> TomlBiMapError)
-> (Text -> Text)
-> Either UnicodeException Text
-> Either TomlBiMapError Text
forall a b c d. (a -> b) -> (c -> d) -> Either a c -> Either b d
forall (p :: * -> * -> *) a b c d.
Bifunctor p =>
(a -> b) -> (c -> d) -> p a c -> p b d
bimap (Text -> TomlBiMapError
ArbitraryError (Text -> TomlBiMapError)
-> (UnicodeException -> Text) -> UnicodeException -> TomlBiMapError
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UnicodeException -> Text
forall a. Show a => a -> Text
tShow) Text -> Text
TL.toStrict (Either UnicodeException Text -> Either TomlBiMapError Text)
-> (ByteString -> Either UnicodeException Text)
-> ByteString
-> Either TomlBiMapError Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Either UnicodeException Text
TL.decodeUtf8'
{-# INLINE _LByteStringText #-}
_LByteString :: TomlBiMap BL.ByteString AnyValue
_LByteString :: TomlBiMap ByteString AnyValue
_LByteString = TomlBiMap ByteString Text
_LByteStringText TomlBiMap ByteString Text
-> TomlBiMap Text AnyValue -> TomlBiMap ByteString AnyValue
forall {k} (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> TomlBiMap Text AnyValue
_Text
{-# INLINE _LByteString #-}
_ByteStringArray :: TomlBiMap ByteString AnyValue
_ByteStringArray :: TomlBiMap ByteString AnyValue
_ByteStringArray = (ByteString -> [Word8])
-> ([Word8] -> ByteString)
-> BiMap TomlBiMapError ByteString [Word8]
forall a b e. (a -> b) -> (b -> a) -> BiMap e a b
iso ByteString -> [Word8]
BS.unpack [Word8] -> ByteString
BS.pack BiMap TomlBiMapError ByteString [Word8]
-> BiMap TomlBiMapError [Word8] AnyValue
-> TomlBiMap ByteString AnyValue
forall {k} (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> TomlBiMap Word8 AnyValue -> BiMap TomlBiMapError [Word8] AnyValue
forall a. TomlBiMap a AnyValue -> TomlBiMap [a] AnyValue
_Array TomlBiMap Word8 AnyValue
_Word8
{-# INLINE _ByteStringArray #-}
_LByteStringArray :: TomlBiMap BL.ByteString AnyValue
_LByteStringArray :: TomlBiMap ByteString AnyValue
_LByteStringArray = (ByteString -> [Word8])
-> ([Word8] -> ByteString)
-> BiMap TomlBiMapError ByteString [Word8]
forall a b e. (a -> b) -> (b -> a) -> BiMap e a b
iso ByteString -> [Word8]
BL.unpack [Word8] -> ByteString
BL.pack BiMap TomlBiMapError ByteString [Word8]
-> BiMap TomlBiMapError [Word8] AnyValue
-> TomlBiMap ByteString AnyValue
forall {k} (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> TomlBiMap Word8 AnyValue -> BiMap TomlBiMapError [Word8] AnyValue
forall a. TomlBiMap a AnyValue -> TomlBiMap [a] AnyValue
_Array TomlBiMap Word8 AnyValue
_Word8
{-# INLINE _LByteStringArray #-}
_Array :: forall a . TomlBiMap a AnyValue -> TomlBiMap [a] AnyValue
_Array :: forall a. TomlBiMap a AnyValue -> TomlBiMap [a] AnyValue
_Array TomlBiMap a AnyValue
elementBimap = ([a] -> Either TomlBiMapError AnyValue)
-> (AnyValue -> Either TomlBiMapError [a])
-> BiMap TomlBiMapError [a] AnyValue
forall e a b. (a -> Either e b) -> (b -> Either e a) -> BiMap e a b
BiMap [a] -> Either TomlBiMapError AnyValue
toAnyValue AnyValue -> Either TomlBiMapError [a]
fromAnyValue
where
toAnyValue :: [a] -> Either TomlBiMapError AnyValue
toAnyValue :: [a] -> Either TomlBiMapError AnyValue
toAnyValue = (a -> Either TomlBiMapError AnyValue)
-> [a] -> Either TomlBiMapError [AnyValue]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM (TomlBiMap a AnyValue -> a -> Either TomlBiMapError AnyValue
forall e a b. BiMap e a b -> a -> Either e b
forward TomlBiMap a AnyValue
elementBimap) ([a] -> Either TomlBiMapError [AnyValue])
-> ([AnyValue] -> Either TomlBiMapError AnyValue)
-> [a]
-> Either TomlBiMapError AnyValue
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> (MatchError -> TomlBiMapError)
-> (Value 'TArray -> AnyValue)
-> Either MatchError (Value 'TArray)
-> Either TomlBiMapError AnyValue
forall a b c d. (a -> b) -> (c -> d) -> Either a c -> Either b d
forall (p :: * -> * -> *) a b c d.
Bifunctor p =>
(a -> b) -> (c -> d) -> p a c -> p b d
bimap MatchError -> TomlBiMapError
WrongValue Value 'TArray -> AnyValue
forall (t :: TValue). Value t -> AnyValue
AnyValue (Either MatchError (Value 'TArray)
-> Either TomlBiMapError AnyValue)
-> ([AnyValue] -> Either MatchError (Value 'TArray))
-> [AnyValue]
-> Either TomlBiMapError AnyValue
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [AnyValue] -> Either MatchError (Value 'TArray)
toMArray
fromAnyValue :: AnyValue -> Either TomlBiMapError [a]
fromAnyValue :: AnyValue -> Either TomlBiMapError [a]
fromAnyValue (AnyValue Value t
v) = (AnyValue -> Either TomlBiMapError a)
-> Value t -> Either TomlBiMapError [a]
forall (t :: TValue).
(AnyValue -> Either TomlBiMapError a)
-> Value t -> Either TomlBiMapError [a]
matchElements (TomlBiMap a AnyValue -> AnyValue -> Either TomlBiMapError a
forall e a b. BiMap e a b -> b -> Either e a
backward TomlBiMap a AnyValue
elementBimap) Value t
v
matchElements :: (AnyValue -> Either TomlBiMapError a) -> Value t -> Either TomlBiMapError [a]
matchElements :: forall (t :: TValue).
(AnyValue -> Either TomlBiMapError a)
-> Value t -> Either TomlBiMapError [a]
matchElements AnyValue -> Either TomlBiMapError a
match (Array [Value t1]
a) = (Value t1 -> Either TomlBiMapError a)
-> [Value t1] -> Either TomlBiMapError [a]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM ((AnyValue -> Either TomlBiMapError a)
-> Value t1 -> Either TomlBiMapError a
forall r (t :: TValue). (AnyValue -> r) -> Value t -> r
applyAsToAny AnyValue -> Either TomlBiMapError a
match) [Value t1]
a
matchElements AnyValue -> Either TomlBiMapError a
_ Value t
val = (MatchError -> TomlBiMapError)
-> Either MatchError [a] -> Either TomlBiMapError [a]
forall a b c. (a -> b) -> Either a c -> Either b c
forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first MatchError -> TomlBiMapError
WrongValue (Either MatchError [a] -> Either TomlBiMapError [a])
-> Either MatchError [a] -> Either TomlBiMapError [a]
forall a b. (a -> b) -> a -> b
$ TValue -> Value t -> Either MatchError [a]
forall (t :: TValue) a. TValue -> Value t -> Either MatchError a
mkMatchError TValue
TArray Value t
val
_NonEmpty :: TomlBiMap a AnyValue -> TomlBiMap (NE.NonEmpty a) AnyValue
_NonEmpty :: forall a. TomlBiMap a AnyValue -> TomlBiMap (NonEmpty a) AnyValue
_NonEmpty TomlBiMap a AnyValue
bi = TomlBiMap (NonEmpty a) [a]
forall a. TomlBiMap (NonEmpty a) [a]
_NonEmptyList TomlBiMap (NonEmpty a) [a]
-> BiMap TomlBiMapError [a] AnyValue
-> BiMap TomlBiMapError (NonEmpty a) AnyValue
forall {k} (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> TomlBiMap a AnyValue -> BiMap TomlBiMapError [a] AnyValue
forall a. TomlBiMap a AnyValue -> TomlBiMap [a] AnyValue
_Array TomlBiMap a AnyValue
bi
{-# INLINE _NonEmpty #-}
_NonEmptyList :: TomlBiMap (NE.NonEmpty a) [a]
_NonEmptyList :: forall a. TomlBiMap (NonEmpty a) [a]
_NonEmptyList = BiMap
{ forward :: NonEmpty a -> Either TomlBiMapError [a]
forward = [a] -> Either TomlBiMapError [a]
forall a b. b -> Either a b
Right ([a] -> Either TomlBiMapError [a])
-> (NonEmpty a -> [a]) -> NonEmpty a -> Either TomlBiMapError [a]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NonEmpty a -> [a]
forall a. NonEmpty a -> [a]
NE.toList
, backward :: [a] -> Either TomlBiMapError (NonEmpty a)
backward = Either TomlBiMapError (NonEmpty a)
-> (NonEmpty a -> Either TomlBiMapError (NonEmpty a))
-> Maybe (NonEmpty a)
-> Either TomlBiMapError (NonEmpty a)
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (TomlBiMapError -> Either TomlBiMapError (NonEmpty a)
forall a b. a -> Either a b
Left (TomlBiMapError -> Either TomlBiMapError (NonEmpty a))
-> TomlBiMapError -> Either TomlBiMapError (NonEmpty a)
forall a b. (a -> b) -> a -> b
$ Text -> TomlBiMapError
ArbitraryError Text
"Empty array list, but expected NonEmpty") NonEmpty a -> Either TomlBiMapError (NonEmpty a)
forall a b. b -> Either a b
Right (Maybe (NonEmpty a) -> Either TomlBiMapError (NonEmpty a))
-> ([a] -> Maybe (NonEmpty a))
-> [a]
-> Either TomlBiMapError (NonEmpty a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [a] -> Maybe (NonEmpty a)
forall a. [a] -> Maybe (NonEmpty a)
NE.nonEmpty
}
{-# INLINE _NonEmptyList #-}
_Set :: (Ord a) => TomlBiMap a AnyValue -> TomlBiMap (S.Set a) AnyValue
_Set :: forall a.
Ord a =>
TomlBiMap a AnyValue -> TomlBiMap (Set a) AnyValue
_Set TomlBiMap a AnyValue
bi = (Set a -> [a])
-> ([a] -> Set a) -> BiMap TomlBiMapError (Set a) [a]
forall a b e. (a -> b) -> (b -> a) -> BiMap e a b
iso Set a -> [a]
forall a. Set a -> [a]
S.toList [a] -> Set a
forall a. Ord a => [a] -> Set a
S.fromList BiMap TomlBiMapError (Set a) [a]
-> BiMap TomlBiMapError [a] AnyValue
-> BiMap TomlBiMapError (Set a) AnyValue
forall {k} (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> TomlBiMap a AnyValue -> BiMap TomlBiMapError [a] AnyValue
forall a. TomlBiMap a AnyValue -> TomlBiMap [a] AnyValue
_Array TomlBiMap a AnyValue
bi
{-# INLINE _Set #-}
_HashSet
#if MIN_VERSION_hashable(1,4,0)
:: (Hashable a)
#else
:: (Eq a, Hashable a)
#endif
=> TomlBiMap a AnyValue
-> TomlBiMap (HS.HashSet a) AnyValue
_HashSet :: forall a.
Hashable a =>
TomlBiMap a AnyValue -> TomlBiMap (HashSet a) AnyValue
_HashSet TomlBiMap a AnyValue
bi = (HashSet a -> [a])
-> ([a] -> HashSet a) -> BiMap TomlBiMapError (HashSet a) [a]
forall a b e. (a -> b) -> (b -> a) -> BiMap e a b
iso HashSet a -> [a]
forall a. HashSet a -> [a]
HS.toList [a] -> HashSet a
forall a. (Eq a, Hashable a) => [a] -> HashSet a
HS.fromList BiMap TomlBiMapError (HashSet a) [a]
-> BiMap TomlBiMapError [a] AnyValue
-> BiMap TomlBiMapError (HashSet a) AnyValue
forall {k} (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> TomlBiMap a AnyValue -> BiMap TomlBiMapError [a] AnyValue
forall a. TomlBiMap a AnyValue -> TomlBiMap [a] AnyValue
_Array TomlBiMap a AnyValue
bi
{-# INLINE _HashSet #-}
_IntSet :: TomlBiMap IS.IntSet AnyValue
_IntSet :: TomlBiMap IntSet AnyValue
_IntSet = (IntSet -> [Int])
-> ([Int] -> IntSet) -> BiMap TomlBiMapError IntSet [Int]
forall a b e. (a -> b) -> (b -> a) -> BiMap e a b
iso IntSet -> [Int]
IS.toList [Int] -> IntSet
IS.fromList BiMap TomlBiMapError IntSet [Int]
-> BiMap TomlBiMapError [Int] AnyValue -> TomlBiMap IntSet AnyValue
forall {k} (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> TomlBiMap Int AnyValue -> BiMap TomlBiMapError [Int] AnyValue
forall a. TomlBiMap a AnyValue -> TomlBiMap [a] AnyValue
_Array TomlBiMap Int AnyValue
_Int
{-# INLINE _IntSet #-}
_Coerce :: (Coercible a b) => TomlBiMap a AnyValue -> TomlBiMap b AnyValue
_Coerce :: forall a b.
Coercible a b =>
TomlBiMap a AnyValue -> TomlBiMap b AnyValue
_Coerce = TomlBiMap a AnyValue -> TomlBiMap b AnyValue
forall a b. Coercible a b => a -> b
coerce
{-# INLINE _Coerce #-}
_ReadString :: (Show a, Read a) => TomlBiMap a String
_ReadString :: forall a. (Show a, Read a) => TomlBiMap a String
_ReadString = (a -> Either TomlBiMapError String)
-> (String -> Either TomlBiMapError a)
-> BiMap TomlBiMapError a String
forall e a b. (a -> Either e b) -> (b -> Either e a) -> BiMap e a b
BiMap (String -> Either TomlBiMapError String
forall a b. b -> Either a b
Right (String -> Either TomlBiMapError String)
-> (a -> String) -> a -> Either TomlBiMapError String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> String
forall a. Show a => a -> String
show) ((String -> TomlBiMapError)
-> Either String a -> Either TomlBiMapError a
forall a b c. (a -> b) -> Either a c -> Either b c
forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first (Text -> TomlBiMapError
ArbitraryError (Text -> TomlBiMapError)
-> (String -> Text) -> String -> TomlBiMapError
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
T.pack) (Either String a -> Either TomlBiMapError a)
-> (String -> Either String a) -> String -> Either TomlBiMapError a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Either String a
forall a. Read a => String -> Either String a
readEither)
{-# INLINE _ReadString #-}
_Read :: (Show a, Read a) => TomlBiMap a AnyValue
_Read :: forall a. (Show a, Read a) => TomlBiMap a AnyValue
_Read = TomlBiMap a String
forall a. (Show a, Read a) => TomlBiMap a String
_ReadString TomlBiMap a String
-> TomlBiMap String AnyValue -> BiMap TomlBiMapError a AnyValue
forall {k} (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> TomlBiMap String AnyValue
_String
{-# INLINE _Read #-}
_TextBy
:: forall a .
(a -> Text)
-> (Text -> Either Text a)
-> TomlBiMap a AnyValue
_TextBy :: forall a.
(a -> Text) -> (Text -> Either Text a) -> TomlBiMap a AnyValue
_TextBy a -> Text
toText Text -> Either Text a
parseText = (a -> Either TomlBiMapError AnyValue)
-> (AnyValue -> Either TomlBiMapError a)
-> BiMap TomlBiMapError a AnyValue
forall e a b. (a -> Either e b) -> (b -> Either e a) -> BiMap e a b
BiMap a -> Either TomlBiMapError AnyValue
toAnyValue AnyValue -> Either TomlBiMapError a
fromAnyValue
where
toAnyValue :: a -> Either TomlBiMapError AnyValue
toAnyValue :: a -> Either TomlBiMapError AnyValue
toAnyValue = AnyValue -> Either TomlBiMapError AnyValue
forall a b. b -> Either a b
Right (AnyValue -> Either TomlBiMapError AnyValue)
-> (a -> AnyValue) -> a -> Either TomlBiMapError AnyValue
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Value 'TText -> AnyValue
forall (t :: TValue). Value t -> AnyValue
AnyValue (Value 'TText -> AnyValue) -> (a -> Value 'TText) -> a -> AnyValue
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Value 'TText
Text (Text -> Value 'TText) -> (a -> Text) -> a -> Value 'TText
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Text
toText
fromAnyValue :: AnyValue -> Either TomlBiMapError a
fromAnyValue :: AnyValue -> Either TomlBiMapError a
fromAnyValue (AnyValue Value t
v) =
(MatchError -> TomlBiMapError)
-> Either MatchError Text -> Either TomlBiMapError Text
forall a b c. (a -> b) -> Either a c -> Either b c
forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first MatchError -> TomlBiMapError
WrongValue (Value t -> Either MatchError Text
forall (t :: TValue). Value t -> Either MatchError Text
matchText Value t
v) Either TomlBiMapError Text
-> (Text -> Either TomlBiMapError a) -> Either TomlBiMapError a
forall a b.
Either TomlBiMapError a
-> (a -> Either TomlBiMapError b) -> Either TomlBiMapError b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (Text -> TomlBiMapError)
-> Either Text a -> Either TomlBiMapError a
forall a b c. (a -> b) -> Either a c -> Either b c
forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first Text -> TomlBiMapError
ArbitraryError (Either Text a -> Either TomlBiMapError a)
-> (Text -> Either Text a) -> Text -> Either TomlBiMapError a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Either Text a
parseText
_Validate :: forall a . (a -> Either Text a) -> TomlBiMap a AnyValue -> TomlBiMap a AnyValue
_Validate :: forall a.
(a -> Either Text a)
-> TomlBiMap a AnyValue -> TomlBiMap a AnyValue
_Validate a -> Either Text a
p BiMap{a -> Either TomlBiMapError AnyValue
AnyValue -> Either TomlBiMapError a
forward :: forall e a b. BiMap e a b -> a -> Either e b
backward :: forall e a b. BiMap e a b -> b -> Either e a
forward :: a -> Either TomlBiMapError AnyValue
backward :: AnyValue -> Either TomlBiMapError a
..} = (a -> Either TomlBiMapError AnyValue)
-> (AnyValue -> Either TomlBiMapError a)
-> BiMap TomlBiMapError a AnyValue
forall e a b. (a -> Either e b) -> (b -> Either e a) -> BiMap e a b
BiMap a -> Either TomlBiMapError AnyValue
forward AnyValue -> Either TomlBiMapError a
backwardWithValidation
where
backwardWithValidation :: AnyValue -> Either TomlBiMapError a
backwardWithValidation :: AnyValue -> Either TomlBiMapError a
backwardWithValidation AnyValue
anyVal = AnyValue -> Either TomlBiMapError a
backward AnyValue
anyVal Either TomlBiMapError a
-> (a -> Either TomlBiMapError a) -> Either TomlBiMapError a
forall a b.
Either TomlBiMapError a
-> (a -> Either TomlBiMapError b) -> Either TomlBiMapError b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (Text -> TomlBiMapError)
-> Either Text a -> Either TomlBiMapError a
forall a b c. (a -> b) -> Either a c -> Either b c
forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first Text -> TomlBiMapError
ArbitraryError (Either Text a -> Either TomlBiMapError a)
-> (a -> Either Text a) -> a -> Either TomlBiMapError a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Either Text a
p
_EnumBoundedText :: forall a. (Show a, Enum a, Bounded a) => TomlBiMap a Text
_EnumBoundedText :: forall a. (Show a, Enum a, Bounded a) => TomlBiMap a Text
_EnumBoundedText = BiMap
{ forward :: a -> Either TomlBiMapError Text
forward = Text -> Either TomlBiMapError Text
forall a b. b -> Either a b
Right (Text -> Either TomlBiMapError Text)
-> (a -> Text) -> a -> Either TomlBiMapError Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Text
forall a. Show a => a -> Text
tShow
, backward :: Text -> Either TomlBiMapError a
backward = Text -> Either TomlBiMapError a
toEnumBounded
}
where
toEnumBounded :: Text -> Either TomlBiMapError a
toEnumBounded :: Text -> Either TomlBiMapError a
toEnumBounded Text
value = case Text -> Map Text a -> Maybe a
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup Text
value Map Text a
enumOptions of
Just a
a -> a -> Either TomlBiMapError a
forall a b. b -> Either a b
Right a
a
Maybe a
Nothing ->
let msg :: Text
msg = Text
"Value is '" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
value Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"' but expected one of: " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text -> [Text] -> Text
T.intercalate Text
", " [Text]
options
in TomlBiMapError -> Either TomlBiMapError a
forall a b. a -> Either a b
Left (Text -> TomlBiMapError
ArbitraryError Text
msg)
where
enumOptions :: Map Text a
enumOptions :: Map Text a
enumOptions = [(Text, a)] -> Map Text a
forall k a. Ord k => [(k, a)] -> Map k a
M.fromList ([(Text, a)] -> Map Text a) -> [(Text, a)] -> Map Text a
forall a b. (a -> b) -> a -> b
$ [Text] -> [a] -> [(Text, a)]
forall a b. [a] -> [b] -> [(a, b)]
zip [Text]
options [a]
enums
options :: [Text]
options = (a -> Text) -> [a] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> Text
forall a. Show a => a -> Text
tShow [a]
enums
enums :: [a]
enums = [forall a. Bounded a => a
minBound @a .. forall a. Bounded a => a
maxBound @a]
_EnumBounded :: (Show a, Enum a, Bounded a) => TomlBiMap a AnyValue
_EnumBounded :: forall a. (Show a, Enum a, Bounded a) => TomlBiMap a AnyValue
_EnumBounded = TomlBiMap a Text
forall a. (Show a, Enum a, Bounded a) => TomlBiMap a Text
_EnumBoundedText TomlBiMap a Text
-> TomlBiMap Text AnyValue -> BiMap TomlBiMapError a AnyValue
forall {k} (cat :: k -> k -> *) (a :: k) (b :: k) (c :: k).
Category cat =>
cat a b -> cat b c -> cat a c
>>> TomlBiMap Text AnyValue
_Text
{-# INLINE _EnumBounded #-}
_Hardcoded :: forall a . (Show a, Eq a) => a -> TomlBiMap a a
_Hardcoded :: forall a. (Show a, Eq a) => a -> TomlBiMap a a
_Hardcoded a
a = BiMap
{ forward :: a -> Either TomlBiMapError a
forward = Either TomlBiMapError a -> a -> Either TomlBiMapError a
forall a b. a -> b -> a
const (a -> Either TomlBiMapError a
forall a b. b -> Either a b
Right a
a)
, backward :: a -> Either TomlBiMapError a
backward = a -> Either TomlBiMapError a
checkValue
}
where
checkValue :: a -> Either TomlBiMapError a
checkValue :: a -> Either TomlBiMapError a
checkValue a
v = if a
v a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== a
a
then a -> Either TomlBiMapError a
forall a b. b -> Either a b
Right a
v
else TomlBiMapError -> Either TomlBiMapError a
forall a b. a -> Either a b
Left (Text -> TomlBiMapError
ArbitraryError Text
msg)
where
msg :: Text
msg :: Text
msg = Text
"Value '" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> String -> Text
T.pack (a -> String
forall a. Show a => a -> String
show a
v)
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"' doesn't align with the hardcoded value '"
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> String -> Text
T.pack (a -> String
forall a. Show a => a -> String
show a
a) Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"'"
_KeyText :: TomlBiMap Key Text
_KeyText :: TomlBiMap Key Text
_KeyText = BiMap
{ forward :: Key -> Either TomlBiMapError Text
forward = Text -> Either TomlBiMapError Text
forall a b. b -> Either a b
Right (Text -> Either TomlBiMapError Text)
-> (Key -> Text) -> Key -> Either TomlBiMapError Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Key -> Text
prettyKey
, backward :: Text -> Either TomlBiMapError Key
backward = (TomlParseError -> TomlBiMapError)
-> Either TomlParseError Key -> Either TomlBiMapError Key
forall a b c. (a -> b) -> Either a c -> Either b c
forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first (Text -> TomlBiMapError
ArbitraryError (Text -> TomlBiMapError)
-> (TomlParseError -> Text) -> TomlParseError -> TomlBiMapError
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TomlParseError -> Text
unTomlParseError) (Either TomlParseError Key -> Either TomlBiMapError Key)
-> (Text -> Either TomlParseError Key)
-> Text
-> Either TomlBiMapError Key
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Either TomlParseError Key
parseKey
}
_KeyString :: TomlBiMap Key String
_KeyString :: TomlBiMap Key String
_KeyString = BiMap
{ forward :: Key -> Either TomlBiMapError String
forward = String -> Either TomlBiMapError String
forall a b. b -> Either a b
Right (String -> Either TomlBiMapError String)
-> (Key -> String) -> Key -> Either TomlBiMapError String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> String
T.unpack (Text -> String) -> (Key -> Text) -> Key -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Key -> Text
prettyKey
, backward :: String -> Either TomlBiMapError Key
backward = (TomlParseError -> TomlBiMapError)
-> Either TomlParseError Key -> Either TomlBiMapError Key
forall a b c. (a -> b) -> Either a c -> Either b c
forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first (Text -> TomlBiMapError
ArbitraryError (Text -> TomlBiMapError)
-> (TomlParseError -> Text) -> TomlParseError -> TomlBiMapError
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TomlParseError -> Text
unTomlParseError) (Either TomlParseError Key -> Either TomlBiMapError Key)
-> (String -> Either TomlParseError Key)
-> String
-> Either TomlBiMapError Key
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Either TomlParseError Key
parseKey (Text -> Either TomlParseError Key)
-> (String -> Text) -> String -> Either TomlParseError Key
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
T.pack
}
_KeyInt :: TomlBiMap Key Int
_KeyInt :: TomlBiMap Key Int
_KeyInt = BiMap
{ forward :: Key -> Either TomlBiMapError Int
forward = (String -> TomlBiMapError)
-> Either String Int -> Either TomlBiMapError Int
forall a b c. (a -> b) -> Either a c -> Either b c
forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first (Text -> TomlBiMapError
ArbitraryError (Text -> TomlBiMapError)
-> (String -> Text) -> String -> TomlBiMapError
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
T.pack) (Either String Int -> Either TomlBiMapError Int)
-> (Key -> Either String Int) -> Key -> Either TomlBiMapError Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Either String Int
forall a. Read a => String -> Either String a
readEither (String -> Either String Int)
-> (Key -> String) -> Key -> Either String Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> String
T.unpack (Text -> String) -> (Key -> Text) -> Key -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Key -> Text
prettyKey
, backward :: Int -> Either TomlBiMapError Key
backward = (TomlParseError -> TomlBiMapError)
-> Either TomlParseError Key -> Either TomlBiMapError Key
forall a b c. (a -> b) -> Either a c -> Either b c
forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first (Text -> TomlBiMapError
ArbitraryError (Text -> TomlBiMapError)
-> (TomlParseError -> Text) -> TomlParseError -> TomlBiMapError
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TomlParseError -> Text
unTomlParseError) (Either TomlParseError Key -> Either TomlBiMapError Key)
-> (Int -> Either TomlParseError Key)
-> Int
-> Either TomlBiMapError Key
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Either TomlParseError Key
parseKey (Text -> Either TomlParseError Key)
-> (Int -> Text) -> Int -> Either TomlParseError Key
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Text
forall a. Show a => a -> Text
tShow
}
_Left :: (Show l, Show r) => TomlBiMap (Either l r) l
_Left :: forall l r. (Show l, Show r) => TomlBiMap (Either l r) l
_Left = (l -> Either l r)
-> (Either l r -> Either TomlBiMapError l)
-> BiMap TomlBiMapError (Either l r) l
forall field object error.
(field -> object)
-> (object -> Either error field) -> BiMap error object field
prism l -> Either l r
forall a b. a -> Either a b
Left ((Either l r -> Either TomlBiMapError l)
-> BiMap TomlBiMapError (Either l r) l)
-> (Either l r -> Either TomlBiMapError l)
-> BiMap TomlBiMapError (Either l r) l
forall a b. (a -> b) -> a -> b
$ \case
Left l
l -> l -> Either TomlBiMapError l
forall a b. b -> Either a b
Right l
l
Either l r
x -> Text -> Either l r -> Either TomlBiMapError l
forall a b. Show a => Text -> a -> Either TomlBiMapError b
wrongConstructor Text
"Left" Either l r
x
_Right :: (Show l, Show r) => TomlBiMap (Either l r) r
_Right :: forall l r. (Show l, Show r) => TomlBiMap (Either l r) r
_Right = (r -> Either l r)
-> (Either l r -> Either TomlBiMapError r)
-> BiMap TomlBiMapError (Either l r) r
forall field object error.
(field -> object)
-> (object -> Either error field) -> BiMap error object field
prism r -> Either l r
forall a b. b -> Either a b
Right ((Either l r -> Either TomlBiMapError r)
-> BiMap TomlBiMapError (Either l r) r)
-> (Either l r -> Either TomlBiMapError r)
-> BiMap TomlBiMapError (Either l r) r
forall a b. (a -> b) -> a -> b
$ \case
Right r
r -> r -> Either TomlBiMapError r
forall a b. b -> Either a b
Right r
r
Either l r
x -> Text -> Either l r -> Either TomlBiMapError r
forall a b. Show a => Text -> a -> Either TomlBiMapError b
wrongConstructor Text
"Right" Either l r
x
_Just :: Show r => TomlBiMap (Maybe r) r
_Just :: forall r. Show r => TomlBiMap (Maybe r) r
_Just = (r -> Maybe r)
-> (Maybe r -> Either TomlBiMapError r)
-> BiMap TomlBiMapError (Maybe r) r
forall field object error.
(field -> object)
-> (object -> Either error field) -> BiMap error object field
prism r -> Maybe r
forall a. a -> Maybe a
Just ((Maybe r -> Either TomlBiMapError r)
-> BiMap TomlBiMapError (Maybe r) r)
-> (Maybe r -> Either TomlBiMapError r)
-> BiMap TomlBiMapError (Maybe r) r
forall a b. (a -> b) -> a -> b
$ \case
Just r
r -> r -> Either TomlBiMapError r
forall a b. b -> Either a b
Right r
r
Maybe r
x -> Text -> Maybe r -> Either TomlBiMapError r
forall a b. Show a => Text -> a -> Either TomlBiMapError b
wrongConstructor Text
"Just" Maybe r
x