{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE Rank2Types #-}
{-# LANGUAGE TypeFamilies #-}
module Toml.Bi.Map
(
BiMap (..)
, TomlBiMap
, invert
, iso
, prism
, TomlBiMapError (..)
, wrongConstructor
, prettyBiMapError
, _Array
, _Bool
, _Double
, _Integer
, _Text
, _LText
, _ZonedTime
, _LocalTime
, _Day
, _TimeOfDay
, _String
, _Read
, _Natural
, _Word
, _Word8
, _Int
, _Float
, _ByteString
, _LByteString
, _ByteStringArray
, _LByteStringArray
, _NonEmpty
, _Set
, _IntSet
, _HashSet
, mkAnyValueBiMap
, _TextBy
, _LTextText
, _NaturalInteger
, _StringText
, _ReadString
, _BoundedInteger
, _EnumBoundedText
, _ByteStringText
, _LByteStringText
, _Left
, _Right
, _EnumBounded
, _Just
, toMArray
) where
import Control.Arrow ((>>>))
import Control.DeepSeq (NFData)
import Control.Monad ((>=>))
import Data.Bifunctor (bimap, first)
import Data.ByteString (ByteString)
import Data.Hashable (Hashable)
import Data.Map (Map)
import Data.Semigroup (Semigroup (..))
import Data.Text (Text)
import Data.Time (Day, LocalTime, TimeOfDay, ZonedTime)
import Data.Word (Word8)
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 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
data BiMap e a b = BiMap
{ BiMap e a b -> a -> Either e b
forward :: a -> Either e b
, BiMap e a b -> b -> Either e a
backward :: b -> Either e a
}
instance Cat.Category (BiMap e) where
id :: BiMap e a a
id :: BiMap e a a
id = (a -> Either e a) -> (a -> Either e a) -> BiMap e a a
forall e a b. (a -> Either e b) -> (b -> Either e a) -> BiMap e a b
BiMap a -> Either e a
forall a b. b -> Either a b
Right a -> Either e a
forall a b. b -> Either a b
Right
{-# INLINE id #-}
(.) :: BiMap e b c -> BiMap e a b -> BiMap e a c
bc :: BiMap e b c
bc . :: BiMap e b c -> BiMap e a b -> BiMap e a c
. ab :: BiMap e a b
ab = BiMap :: forall e a b. (a -> Either e b) -> (b -> Either e a) -> BiMap e a b
BiMap
{ forward :: a -> Either e c
forward = BiMap e a b -> a -> Either e b
forall e a b. BiMap e a b -> a -> Either e b
forward BiMap e a b
ab (a -> Either e b) -> (b -> Either e c) -> a -> Either e c
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> BiMap e b c -> b -> Either e c
forall e a b. BiMap e a b -> a -> Either e b
forward BiMap e b c
bc
, backward :: c -> Either e a
backward = BiMap e b c -> c -> Either e b
forall e a b. BiMap e a b -> b -> Either e a
backward BiMap e b c
bc (c -> Either e b) -> (b -> Either e a) -> c -> Either e a
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> BiMap e a b -> b -> Either e a
forall e a b. BiMap e a b -> b -> Either e a
backward BiMap e a b
ab
}
{-# INLINE (.) #-}
invert :: BiMap e a b -> BiMap e b a
invert :: BiMap e a b -> BiMap e b a
invert (BiMap f :: a -> Either e b
f g :: b -> Either e a
g) = (b -> Either e a) -> (a -> Either e b) -> BiMap e b a
forall e a b. (a -> Either e b) -> (b -> Either e a) -> BiMap e a b
BiMap b -> Either e a
g a -> Either e b
f
{-# INLINE invert #-}
iso :: (a -> b) -> (b -> a) -> BiMap e a b
iso :: (a -> b) -> (b -> a) -> BiMap e a b
iso f :: a -> b
f g :: b -> a
g = (a -> Either e b) -> (b -> Either e a) -> BiMap e a b
forall e a b. (a -> Either e b) -> (b -> Either e a) -> BiMap e a b
BiMap (b -> Either e b
forall a b. b -> Either a b
Right (b -> Either e b) -> (a -> b) -> a -> Either e b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> b
f) (a -> Either e a
forall a b. b -> Either a b
Right (a -> Either e a) -> (b -> a) -> b -> Either e a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. b -> a
g)
{-# INLINE iso #-}
prism
:: (field -> object)
-> (object -> Either error field)
-> BiMap error object field
prism :: (field -> object)
-> (object -> Either error field) -> BiMap error object field
prism review :: field -> object
review preview :: object -> Either error field
preview = (object -> Either error field)
-> (field -> Either error object) -> BiMap error object field
forall e a b. (a -> Either e b) -> (b -> Either e a) -> BiMap e a b
BiMap object -> Either error field
preview (object -> Either error object
forall a b. b -> Either a b
Right (object -> Either error object)
-> (field -> object) -> field -> Either error object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. field -> object
review)
{-# INLINE prism #-}
type TomlBiMap = BiMap TomlBiMapError
data TomlBiMapError
= WrongConstructor
!Text
!Text
| WrongValue
!MatchError
| ArbitraryError
!Text
deriving stock (TomlBiMapError -> TomlBiMapError -> Bool
(TomlBiMapError -> TomlBiMapError -> Bool)
-> (TomlBiMapError -> TomlBiMapError -> Bool) -> Eq TomlBiMapError
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TomlBiMapError -> TomlBiMapError -> Bool
$c/= :: TomlBiMapError -> TomlBiMapError -> Bool
== :: TomlBiMapError -> TomlBiMapError -> Bool
$c== :: TomlBiMapError -> TomlBiMapError -> Bool
Eq, Int -> TomlBiMapError -> ShowS
[TomlBiMapError] -> ShowS
TomlBiMapError -> String
(Int -> TomlBiMapError -> ShowS)
-> (TomlBiMapError -> String)
-> ([TomlBiMapError] -> ShowS)
-> Show TomlBiMapError
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TomlBiMapError] -> ShowS
$cshowList :: [TomlBiMapError] -> ShowS
show :: TomlBiMapError -> String
$cshow :: TomlBiMapError -> String
showsPrec :: Int -> TomlBiMapError -> ShowS
$cshowsPrec :: Int -> TomlBiMapError -> ShowS
Show, (forall x. TomlBiMapError -> Rep TomlBiMapError x)
-> (forall x. Rep TomlBiMapError x -> TomlBiMapError)
-> Generic TomlBiMapError
forall x. Rep TomlBiMapError x -> TomlBiMapError
forall x. TomlBiMapError -> Rep TomlBiMapError x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TomlBiMapError x -> TomlBiMapError
$cfrom :: forall x. TomlBiMapError -> Rep TomlBiMapError x
Generic)
deriving anyclass (TomlBiMapError -> ()
(TomlBiMapError -> ()) -> NFData TomlBiMapError
forall a. (a -> ()) -> NFData a
rnf :: TomlBiMapError -> ()
$crnf :: TomlBiMapError -> ()
NFData)
prettyBiMapError :: TomlBiMapError -> Text
prettyBiMapError :: TomlBiMapError -> Text
prettyBiMapError = \case
WrongConstructor expected :: Text
expected actual :: Text
actual -> [Text] -> Text
T.unlines
[ "Invalid constructor"
, " * Expected: " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
expected
, " * Actual: " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
actual
]
WrongValue (MatchError expected :: TValue
expected actual :: AnyValue
actual) -> [Text] -> Text
T.unlines
[ "Invalid constructor"
, " * Expected: " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> TValue -> Text
forall a. Show a => a -> Text
tShow TValue
expected
, " * Actual: " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> AnyValue -> Text
forall a. Show a => a -> Text
tShow AnyValue
actual
]
ArbitraryError text :: Text
text -> Text
text
wrongConstructor
:: Show a
=> Text
-> a
-> Either TomlBiMapError b
wrongConstructor :: Text -> a -> Either TomlBiMapError b
wrongConstructor constructor :: Text
constructor x :: a
x = TomlBiMapError -> Either TomlBiMapError b
forall a b. a -> Either a b
Left (TomlBiMapError -> Either TomlBiMapError b)
-> TomlBiMapError -> Either TomlBiMapError b
forall a b. (a -> b) -> a -> b
$ Text -> Text -> TomlBiMapError
WrongConstructor Text
constructor (a -> Text
forall a. Show a => a -> Text
tShow a
x)
_Left :: (Show l, Show r) => TomlBiMap (Either l r) l
_Left :: TomlBiMap (Either l r) l
_Left = (l -> Either l r)
-> (Either l r -> Either TomlBiMapError l)
-> TomlBiMap (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)
-> TomlBiMap (Either l r) l)
-> (Either l r -> Either TomlBiMapError l)
-> TomlBiMap (Either l r) l
forall a b. (a -> b) -> a -> b
$ \case
Left l :: l
l -> l -> Either TomlBiMapError l
forall a b. b -> Either a b
Right l
l
x :: Either l r
x -> Text -> Either l r -> Either TomlBiMapError l
forall a b. Show a => Text -> a -> Either TomlBiMapError b
wrongConstructor "Left" Either l r
x
_Right :: (Show l, Show r) => TomlBiMap (Either l r) r
_Right :: TomlBiMap (Either l r) r
_Right = (r -> Either l r)
-> (Either l r -> Either TomlBiMapError r)
-> TomlBiMap (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)
-> TomlBiMap (Either l r) r)
-> (Either l r -> Either TomlBiMapError r)
-> TomlBiMap (Either l r) r
forall a b. (a -> b) -> a -> b
$ \case
Right r :: r
r -> r -> Either TomlBiMapError r
forall a b. b -> Either a b
Right r
r
x :: Either l r
x -> Text -> Either l r -> Either TomlBiMapError r
forall a b. Show a => Text -> a -> Either TomlBiMapError b
wrongConstructor "Right" Either l r
x
_Just :: Show r => TomlBiMap (Maybe r) r
_Just :: TomlBiMap (Maybe r) r
_Just = (r -> Maybe r)
-> (Maybe r -> Either TomlBiMapError r) -> TomlBiMap (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) -> TomlBiMap (Maybe r) r)
-> (Maybe r -> Either TomlBiMapError r) -> TomlBiMap (Maybe r) r
forall a b. (a -> b) -> a -> b
$ \case
Just r :: r
r -> r -> Either TomlBiMapError r
forall a b. b -> Either a b
Right r
r
x :: Maybe r
x -> Text -> Maybe r -> Either TomlBiMapError r
forall a b. Show a => Text -> a -> Either TomlBiMapError b
wrongConstructor "Just" Maybe r
x
mkAnyValueBiMap
:: forall a (tag :: TValue) . (forall (t :: TValue) . Value t -> Either MatchError a)
-> (a -> Value tag)
-> TomlBiMap a AnyValue
mkAnyValueBiMap :: (forall (t :: TValue). Value t -> Either MatchError a)
-> (a -> Value tag) -> TomlBiMap a AnyValue
mkAnyValueBiMap matchValue :: forall (t :: TValue). Value t -> Either MatchError a
matchValue toValue :: a -> Value tag
toValue = BiMap :: forall e a b. (a -> Either e b) -> (b -> Either e a) -> BiMap e a b
BiMap
{ forward :: a -> Either TomlBiMapError AnyValue
forward = 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
. a -> AnyValue
toAnyValue
, backward :: AnyValue -> Either TomlBiMapError a
backward = AnyValue -> Either TomlBiMapError a
fromAnyValue
}
where
toAnyValue :: a -> AnyValue
toAnyValue :: a -> AnyValue
toAnyValue = Value tag -> AnyValue
forall (t :: TValue). Value t -> AnyValue
AnyValue (Value tag -> AnyValue) -> (a -> Value tag) -> a -> AnyValue
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Value tag
toValue
fromAnyValue :: AnyValue -> Either TomlBiMapError a
fromAnyValue :: AnyValue -> Either TomlBiMapError a
fromAnyValue (AnyValue value :: Value t
value) = (MatchError -> TomlBiMapError)
-> Either MatchError a -> Either TomlBiMapError a
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
$ Value t -> Either MatchError a
forall (t :: TValue). Value t -> Either MatchError a
matchValue Value t
value
_TextBy
:: forall a .
(a -> Text)
-> (Text -> Either Text a)
-> TomlBiMap a AnyValue
_TextBy :: (a -> Text) -> (Text -> Either Text a) -> TomlBiMap a AnyValue
_TextBy toText :: a -> Text
toText parseText :: Text -> Either Text a
parseText = (a -> Either TomlBiMapError AnyValue)
-> (AnyValue -> Either TomlBiMapError a) -> TomlBiMap 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 v :: Value t
v) =
(MatchError -> TomlBiMapError)
-> Either MatchError Text -> Either TomlBiMapError Text
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 (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (Text -> TomlBiMapError)
-> Either Text a -> Either TomlBiMapError a
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
_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 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 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 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 forall (t :: TValue). Value t -> Either MatchError Text
matchText Text -> Value 'TText
Text
{-# INLINE _Text #-}
_LTextText :: BiMap e TL.Text Text
_LTextText :: 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 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 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 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 forall (t :: TValue). Value t -> Either MatchError TimeOfDay
matchHours TimeOfDay -> Value 'THours
Hours
{-# INLINE _TimeOfDay #-}
_StringText :: BiMap e String Text
_StringText :: 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 #-}
_ReadString :: (Show a, Read a) => TomlBiMap a String
_ReadString :: TomlBiMap a String
_ReadString = (a -> Either TomlBiMapError String)
-> (String -> Either TomlBiMapError a) -> TomlBiMap 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 (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 :: TomlBiMap a AnyValue
_Read = TomlBiMap a String
forall a. (Show a, Read a) => TomlBiMap a String
_ReadString TomlBiMap a String
-> TomlBiMap String AnyValue -> TomlBiMap 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 #-}
_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 n :: Integer
n
| Integer
n Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
< 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
$ "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 :: TomlBiMap a Integer
_BoundedInteger = (a -> Either TomlBiMapError Integer)
-> (Integer -> Either TomlBiMapError a) -> TomlBiMap 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 :: Integer -> Either TomlBiMapError a
eitherBounded n :: Integer
n
| Integer
n Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
< a -> Integer
forall a. Integral a => a -> Integer
toInteger (Bounded a => a
forall a. Bounded a => a
minBound @a) =
let msg :: Text
msg = "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
<> " is less than minBound: " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> a -> Text
forall a. Show a => a -> Text
tShow (Bounded a => a
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 (Bounded a => a
forall a. Bounded a => a
maxBound @a) =
let msg :: Text
msg = "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
<> " is greater than maxBound: " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> a -> Text
forall a. Show a => a -> Text
tShow (Bounded a => a
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)
_EnumBoundedText :: forall a. (Show a, Enum a, Bounded a) => TomlBiMap a Text
_EnumBoundedText :: TomlBiMap a Text
_EnumBoundedText = BiMap :: forall e a b. (a -> Either e b) -> (b -> Either e a) -> BiMap e a b
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 value :: 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 -> a -> Either TomlBiMapError a
forall a b. b -> Either a b
Right a
a
Nothing ->
let msg :: Text
msg = "Value is '" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
value Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> "' but expected one of: " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text -> [Text] -> Text
T.intercalate ", " [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 (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 = [Bounded a => a
forall a. Bounded a => a
minBound @a .. Bounded a => a
forall a. Bounded a => a
maxBound @a]
_EnumBounded :: (Show a, Enum a, Bounded a) => TomlBiMap a AnyValue
_EnumBounded :: 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 -> TomlBiMap 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 #-}
_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 (\err :: 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 (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 :: TomlBiMap a AnyValue -> TomlBiMap [a] AnyValue
_Array elementBimap :: TomlBiMap a AnyValue
elementBimap = ([a] -> Either TomlBiMapError AnyValue)
-> (AnyValue -> Either TomlBiMapError [a])
-> TomlBiMap [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)
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 (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 v :: 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 :: (AnyValue -> Either TomlBiMapError a)
-> Value t -> Either TomlBiMapError [a]
matchElements match :: AnyValue -> Either TomlBiMapError a
match (Array a :: [Value t]
a) = (Value t -> Either TomlBiMapError a)
-> [Value t] -> Either TomlBiMapError [a]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM ((AnyValue -> Either TomlBiMapError a)
-> Value t -> Either TomlBiMapError a
forall r (t :: TValue). (AnyValue -> r) -> Value t -> r
applyAsToAny AnyValue -> Either TomlBiMapError a
match) [Value t]
a
matchElements _ val :: Value t
val = (MatchError -> TomlBiMapError)
-> Either MatchError [a] -> Either TomlBiMapError [a]
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 :: TomlBiMap a AnyValue -> TomlBiMap (NonEmpty a) AnyValue
_NonEmpty bi :: TomlBiMap a AnyValue
bi = TomlBiMap (NonEmpty a) [a]
forall a. TomlBiMap (NonEmpty a) [a]
_NonEmptyArray TomlBiMap (NonEmpty a) [a]
-> BiMap TomlBiMapError [a] AnyValue
-> TomlBiMap (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 #-}
_NonEmptyArray :: TomlBiMap (NE.NonEmpty a) [a]
_NonEmptyArray :: TomlBiMap (NonEmpty a) [a]
_NonEmptyArray = BiMap :: forall e a b. (a -> Either e b) -> (b -> Either e a) -> BiMap e a b
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 "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 _NonEmptyArray #-}
_Set :: (Ord a) => TomlBiMap a AnyValue -> TomlBiMap (S.Set a) AnyValue
_Set :: TomlBiMap a AnyValue -> TomlBiMap (Set a) AnyValue
_Set bi :: 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 -> TomlBiMap (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 :: (Eq a, Hashable a) => TomlBiMap a AnyValue -> TomlBiMap (HS.HashSet a) AnyValue
_HashSet :: TomlBiMap a AnyValue -> TomlBiMap (HashSet a) AnyValue
_HashSet bi :: 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
-> TomlBiMap (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 #-}
tShow :: Show a => a -> Text
tShow :: a -> Text
tShow = String -> Text
T.pack (String -> Text) -> (a -> String) -> a -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> String
forall a. Show a => a -> String
show
{-# INLINE tShow #-}