{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE DataKinds                  #-}
{-# LANGUAGE DeriveAnyClass             #-}
{-# LANGUAGE DeriveTraversable          #-}
{-# LANGUAGE DeriveGeneric              #-}
{-# LANGUAGE DerivingStrategies         #-}
{-# LANGUAGE TypeOperators              #-}

-- | Common types that aren't in the specification
module Language.LSP.Types.Common (
    type (|?) (..)
  , toEither
  , List (..)
  , Empty (..)
  , Int32
  , UInt ) where

import Control.Applicative
import Control.DeepSeq
import Data.Aeson
import Data.Int (Int32)
import Data.Mod.Word
import Text.Read (Read(readPrec))
import GHC.Generics hiding (UInt)
import GHC.TypeNats hiding (Mod)
import Data.Bifunctor (bimap)

-- | The "uinteger" type in the LSP spec.
--
-- Unusually, this is a **31**-bit unsigned integer, not a 32-bit one.
newtype UInt = UInt (Mod (2^31))
  deriving newtype (Integer -> UInt
UInt -> UInt
UInt -> UInt -> UInt
(UInt -> UInt -> UInt)
-> (UInt -> UInt -> UInt)
-> (UInt -> UInt -> UInt)
-> (UInt -> UInt)
-> (UInt -> UInt)
-> (UInt -> UInt)
-> (Integer -> UInt)
-> Num UInt
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
fromInteger :: Integer -> UInt
$cfromInteger :: Integer -> UInt
signum :: UInt -> UInt
$csignum :: UInt -> UInt
abs :: UInt -> UInt
$cabs :: UInt -> UInt
negate :: UInt -> UInt
$cnegate :: UInt -> UInt
* :: UInt -> UInt -> UInt
$c* :: UInt -> UInt -> UInt
- :: UInt -> UInt -> UInt
$c- :: UInt -> UInt -> UInt
+ :: UInt -> UInt -> UInt
$c+ :: UInt -> UInt -> UInt
Num, UInt
UInt -> UInt -> Bounded UInt
forall a. a -> a -> Bounded a
maxBound :: UInt
$cmaxBound :: UInt
minBound :: UInt
$cminBound :: UInt
Bounded, Int -> UInt
UInt -> Int
UInt -> [UInt]
UInt -> UInt
UInt -> UInt -> [UInt]
UInt -> UInt -> UInt -> [UInt]
(UInt -> UInt)
-> (UInt -> UInt)
-> (Int -> UInt)
-> (UInt -> Int)
-> (UInt -> [UInt])
-> (UInt -> UInt -> [UInt])
-> (UInt -> UInt -> [UInt])
-> (UInt -> UInt -> UInt -> [UInt])
-> Enum UInt
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: UInt -> UInt -> UInt -> [UInt]
$cenumFromThenTo :: UInt -> UInt -> UInt -> [UInt]
enumFromTo :: UInt -> UInt -> [UInt]
$cenumFromTo :: UInt -> UInt -> [UInt]
enumFromThen :: UInt -> UInt -> [UInt]
$cenumFromThen :: UInt -> UInt -> [UInt]
enumFrom :: UInt -> [UInt]
$cenumFrom :: UInt -> [UInt]
fromEnum :: UInt -> Int
$cfromEnum :: UInt -> Int
toEnum :: Int -> UInt
$ctoEnum :: Int -> UInt
pred :: UInt -> UInt
$cpred :: UInt -> UInt
succ :: UInt -> UInt
$csucc :: UInt -> UInt
Enum, UInt -> UInt -> Bool
(UInt -> UInt -> Bool) -> (UInt -> UInt -> Bool) -> Eq UInt
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UInt -> UInt -> Bool
$c/= :: UInt -> UInt -> Bool
== :: UInt -> UInt -> Bool
$c== :: UInt -> UInt -> Bool
Eq, Eq UInt
Eq UInt
-> (UInt -> UInt -> Ordering)
-> (UInt -> UInt -> Bool)
-> (UInt -> UInt -> Bool)
-> (UInt -> UInt -> Bool)
-> (UInt -> UInt -> Bool)
-> (UInt -> UInt -> UInt)
-> (UInt -> UInt -> UInt)
-> Ord UInt
UInt -> UInt -> Bool
UInt -> UInt -> Ordering
UInt -> UInt -> UInt
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: UInt -> UInt -> UInt
$cmin :: UInt -> UInt -> UInt
max :: UInt -> UInt -> UInt
$cmax :: UInt -> UInt -> UInt
>= :: UInt -> UInt -> Bool
$c>= :: UInt -> UInt -> Bool
> :: UInt -> UInt -> Bool
$c> :: UInt -> UInt -> Bool
<= :: UInt -> UInt -> Bool
$c<= :: UInt -> UInt -> Bool
< :: UInt -> UInt -> Bool
$c< :: UInt -> UInt -> Bool
compare :: UInt -> UInt -> Ordering
$ccompare :: UInt -> UInt -> Ordering
$cp1Ord :: Eq UInt
Ord)
  deriving stock ((forall x. UInt -> Rep UInt x)
-> (forall x. Rep UInt x -> UInt) -> Generic UInt
forall x. Rep UInt x -> UInt
forall x. UInt -> Rep UInt x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UInt x -> UInt
$cfrom :: forall x. UInt -> Rep UInt x
Generic)
  deriving anyclass (UInt -> ()
(UInt -> ()) -> NFData UInt
forall a. (a -> ()) -> NFData a
rnf :: UInt -> ()
$crnf :: UInt -> ()
NFData)

instance Show UInt where
  show :: UInt -> String
show (UInt Mod (2 ^ 31)
u) = Word -> String
forall a. Show a => a -> String
show (Word -> String) -> Word -> String
forall a b. (a -> b) -> a -> b
$ Mod 2147483648 -> Word
forall (m :: Nat). Mod m -> Word
unMod Mod 2147483648
Mod (2 ^ 31)
u

instance Read UInt where
  readPrec :: ReadPrec UInt
readPrec = Integer -> UInt
forall a. Num a => Integer -> a
fromInteger (Integer -> UInt) -> ReadPrec Integer -> ReadPrec UInt
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReadPrec Integer
forall a. Read a => ReadPrec a
readPrec

instance Real UInt where
  toRational :: UInt -> Rational
toRational (UInt Mod (2 ^ 31)
u) = Word -> Rational
forall a. Real a => a -> Rational
toRational (Word -> Rational) -> Word -> Rational
forall a b. (a -> b) -> a -> b
$ Mod 2147483648 -> Word
forall (m :: Nat). Mod m -> Word
unMod Mod 2147483648
Mod (2 ^ 31)
u

instance Integral UInt where
  quotRem :: UInt -> UInt -> (UInt, UInt)
quotRem (UInt Mod (2 ^ 31)
x) (UInt Mod (2 ^ 31)
y) = (Word -> UInt) -> (Word -> UInt) -> (Word, Word) -> (UInt, UInt)
forall (p :: * -> * -> *) a b c d.
Bifunctor p =>
(a -> b) -> (c -> d) -> p a c -> p b d
bimap Word -> UInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word -> UInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral ((Word, Word) -> (UInt, UInt)) -> (Word, Word) -> (UInt, UInt)
forall a b. (a -> b) -> a -> b
$ Word -> Word -> (Word, Word)
forall a. Integral a => a -> a -> (a, a)
quotRem (Mod 2147483648 -> Word
forall (m :: Nat). Mod m -> Word
unMod Mod 2147483648
Mod (2 ^ 31)
x) (Mod 2147483648 -> Word
forall (m :: Nat). Mod m -> Word
unMod Mod 2147483648
Mod (2 ^ 31)
y)
  toInteger :: UInt -> Integer
toInteger (UInt Mod (2 ^ 31)
u) = Word -> Integer
forall a. Integral a => a -> Integer
toInteger (Word -> Integer) -> Word -> Integer
forall a b. (a -> b) -> a -> b
$ Mod 2147483648 -> Word
forall (m :: Nat). Mod m -> Word
unMod Mod 2147483648
Mod (2 ^ 31)
u

instance ToJSON UInt where
  toJSON :: UInt -> Value
toJSON UInt
u = Integer -> Value
forall a. ToJSON a => a -> Value
toJSON (UInt -> Integer
forall a. Integral a => a -> Integer
toInteger UInt
u)

instance FromJSON UInt where
  parseJSON :: Value -> Parser UInt
parseJSON Value
v = Integer -> UInt
forall a. Num a => Integer -> a
fromInteger (Integer -> UInt) -> Parser Integer -> Parser UInt
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser Integer
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v

-- | A terser, isomorphic data type for 'Either', that does not get tagged when
-- converting to and from JSON.
data a |? b = InL a
            | InR b
  deriving (ReadPrec [a |? b]
ReadPrec (a |? b)
Int -> ReadS (a |? b)
ReadS [a |? b]
(Int -> ReadS (a |? b))
-> ReadS [a |? b]
-> ReadPrec (a |? b)
-> ReadPrec [a |? b]
-> Read (a |? b)
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
forall a b. (Read a, Read b) => ReadPrec [a |? b]
forall a b. (Read a, Read b) => ReadPrec (a |? b)
forall a b. (Read a, Read b) => Int -> ReadS (a |? b)
forall a b. (Read a, Read b) => ReadS [a |? b]
readListPrec :: ReadPrec [a |? b]
$creadListPrec :: forall a b. (Read a, Read b) => ReadPrec [a |? b]
readPrec :: ReadPrec (a |? b)
$creadPrec :: forall a b. (Read a, Read b) => ReadPrec (a |? b)
readList :: ReadS [a |? b]
$creadList :: forall a b. (Read a, Read b) => ReadS [a |? b]
readsPrec :: Int -> ReadS (a |? b)
$creadsPrec :: forall a b. (Read a, Read b) => Int -> ReadS (a |? b)
Read,Int -> (a |? b) -> ShowS
[a |? b] -> ShowS
(a |? b) -> String
(Int -> (a |? b) -> ShowS)
-> ((a |? b) -> String) -> ([a |? b] -> ShowS) -> Show (a |? b)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall a b. (Show a, Show b) => Int -> (a |? b) -> ShowS
forall a b. (Show a, Show b) => [a |? b] -> ShowS
forall a b. (Show a, Show b) => (a |? b) -> String
showList :: [a |? b] -> ShowS
$cshowList :: forall a b. (Show a, Show b) => [a |? b] -> ShowS
show :: (a |? b) -> String
$cshow :: forall a b. (Show a, Show b) => (a |? b) -> String
showsPrec :: Int -> (a |? b) -> ShowS
$cshowsPrec :: forall a b. (Show a, Show b) => Int -> (a |? b) -> ShowS
Show,(a |? b) -> (a |? b) -> Bool
((a |? b) -> (a |? b) -> Bool)
-> ((a |? b) -> (a |? b) -> Bool) -> Eq (a |? b)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall a b. (Eq a, Eq b) => (a |? b) -> (a |? b) -> Bool
/= :: (a |? b) -> (a |? b) -> Bool
$c/= :: forall a b. (Eq a, Eq b) => (a |? b) -> (a |? b) -> Bool
== :: (a |? b) -> (a |? b) -> Bool
$c== :: forall a b. (Eq a, Eq b) => (a |? b) -> (a |? b) -> Bool
Eq,Eq (a |? b)
Eq (a |? b)
-> ((a |? b) -> (a |? b) -> Ordering)
-> ((a |? b) -> (a |? b) -> Bool)
-> ((a |? b) -> (a |? b) -> Bool)
-> ((a |? b) -> (a |? b) -> Bool)
-> ((a |? b) -> (a |? b) -> Bool)
-> ((a |? b) -> (a |? b) -> a |? b)
-> ((a |? b) -> (a |? b) -> a |? b)
-> Ord (a |? b)
(a |? b) -> (a |? b) -> Bool
(a |? b) -> (a |? b) -> Ordering
(a |? b) -> (a |? b) -> a |? b
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall a b. (Ord a, Ord b) => Eq (a |? b)
forall a b. (Ord a, Ord b) => (a |? b) -> (a |? b) -> Bool
forall a b. (Ord a, Ord b) => (a |? b) -> (a |? b) -> Ordering
forall a b. (Ord a, Ord b) => (a |? b) -> (a |? b) -> a |? b
min :: (a |? b) -> (a |? b) -> a |? b
$cmin :: forall a b. (Ord a, Ord b) => (a |? b) -> (a |? b) -> a |? b
max :: (a |? b) -> (a |? b) -> a |? b
$cmax :: forall a b. (Ord a, Ord b) => (a |? b) -> (a |? b) -> a |? b
>= :: (a |? b) -> (a |? b) -> Bool
$c>= :: forall a b. (Ord a, Ord b) => (a |? b) -> (a |? b) -> Bool
> :: (a |? b) -> (a |? b) -> Bool
$c> :: forall a b. (Ord a, Ord b) => (a |? b) -> (a |? b) -> Bool
<= :: (a |? b) -> (a |? b) -> Bool
$c<= :: forall a b. (Ord a, Ord b) => (a |? b) -> (a |? b) -> Bool
< :: (a |? b) -> (a |? b) -> Bool
$c< :: forall a b. (Ord a, Ord b) => (a |? b) -> (a |? b) -> Bool
compare :: (a |? b) -> (a |? b) -> Ordering
$ccompare :: forall a b. (Ord a, Ord b) => (a |? b) -> (a |? b) -> Ordering
$cp1Ord :: forall a b. (Ord a, Ord b) => Eq (a |? b)
Ord,(forall x. (a |? b) -> Rep (a |? b) x)
-> (forall x. Rep (a |? b) x -> a |? b) -> Generic (a |? b)
forall x. Rep (a |? b) x -> a |? b
forall x. (a |? b) -> Rep (a |? b) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall a b x. Rep (a |? b) x -> a |? b
forall a b x. (a |? b) -> Rep (a |? b) x
$cto :: forall a b x. Rep (a |? b) x -> a |? b
$cfrom :: forall a b x. (a |? b) -> Rep (a |? b) x
Generic)
infixr |?

toEither :: a |? b -> Either a b
toEither :: (a |? b) -> Either a b
toEither (InL a
a) = a -> Either a b
forall a b. a -> Either a b
Left a
a
toEither (InR b
b) = b -> Either a b
forall a b. b -> Either a b
Right b
b

instance (ToJSON a, ToJSON b) => ToJSON (a |? b) where
  toJSON :: (a |? b) -> Value
toJSON (InL a
x) = a -> Value
forall a. ToJSON a => a -> Value
toJSON a
x
  toJSON (InR b
x) = b -> Value
forall a. ToJSON a => a -> Value
toJSON b
x

instance (FromJSON a, FromJSON b) => FromJSON (a |? b) where
  -- Important: Try to parse the **rightmost** type first, as in the specification
  -- the more complex types tend to appear on the right of the |, i.e.
  -- @colorProvider?: boolean | DocumentColorOptions | DocumentColorRegistrationOptions;@
  parseJSON :: Value -> Parser (a |? b)
parseJSON Value
v = b -> a |? b
forall a b. b -> a |? b
InR (b -> a |? b) -> Parser b -> Parser (a |? b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser b
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v Parser (a |? b) -> Parser (a |? b) -> Parser (a |? b)
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> a -> a |? b
forall a b. a -> a |? b
InL (a -> a |? b) -> Parser a -> Parser (a |? b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser a
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v

instance (NFData a, NFData b) => NFData (a |? b)

-- | All LSP types representing a list **must** use this type rather than '[]'.
-- In particular this is necessary to change the 'FromJSON' instance to be compatible
-- with Elisp (where empty lists show up as 'null')
newtype List a = List [a]
    deriving stock (Functor List
Foldable List
Functor List
-> Foldable List
-> (forall (f :: * -> *) a b.
    Applicative f =>
    (a -> f b) -> List a -> f (List b))
-> (forall (f :: * -> *) a.
    Applicative f =>
    List (f a) -> f (List a))
-> (forall (m :: * -> *) a b.
    Monad m =>
    (a -> m b) -> List a -> m (List b))
-> (forall (m :: * -> *) a. Monad m => List (m a) -> m (List a))
-> Traversable List
(a -> f b) -> List a -> f (List b)
forall (t :: * -> *).
Functor t
-> Foldable t
-> (forall (f :: * -> *) a b.
    Applicative f =>
    (a -> f b) -> t a -> f (t b))
-> (forall (f :: * -> *) a. Applicative f => t (f a) -> f (t a))
-> (forall (m :: * -> *) a b.
    Monad m =>
    (a -> m b) -> t a -> m (t b))
-> (forall (m :: * -> *) a. Monad m => t (m a) -> m (t a))
-> Traversable t
forall (m :: * -> *) a. Monad m => List (m a) -> m (List a)
forall (f :: * -> *) a. Applicative f => List (f a) -> f (List a)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> List a -> m (List b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> List a -> f (List b)
sequence :: List (m a) -> m (List a)
$csequence :: forall (m :: * -> *) a. Monad m => List (m a) -> m (List a)
mapM :: (a -> m b) -> List a -> m (List b)
$cmapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> List a -> m (List b)
sequenceA :: List (f a) -> f (List a)
$csequenceA :: forall (f :: * -> *) a. Applicative f => List (f a) -> f (List a)
traverse :: (a -> f b) -> List a -> f (List b)
$ctraverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> List a -> f (List b)
$cp2Traversable :: Foldable List
$cp1Traversable :: Functor List
Traversable,(forall x. List a -> Rep (List a) x)
-> (forall x. Rep (List a) x -> List a) -> Generic (List a)
forall x. Rep (List a) x -> List a
forall x. List a -> Rep (List a) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall a x. Rep (List a) x -> List a
forall a x. List a -> Rep (List a) x
$cto :: forall a x. Rep (List a) x -> List a
$cfrom :: forall a x. List a -> Rep (List a) x
Generic)
    deriving newtype (Int -> List a -> ShowS
[List a] -> ShowS
List a -> String
(Int -> List a -> ShowS)
-> (List a -> String) -> ([List a] -> ShowS) -> Show (List a)
forall a. Show a => Int -> List a -> ShowS
forall a. Show a => [List a] -> ShowS
forall a. Show a => List a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [List a] -> ShowS
$cshowList :: forall a. Show a => [List a] -> ShowS
show :: List a -> String
$cshow :: forall a. Show a => List a -> String
showsPrec :: Int -> List a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> List a -> ShowS
Show,ReadPrec [List a]
ReadPrec (List a)
Int -> ReadS (List a)
ReadS [List a]
(Int -> ReadS (List a))
-> ReadS [List a]
-> ReadPrec (List a)
-> ReadPrec [List a]
-> Read (List a)
forall a. Read a => ReadPrec [List a]
forall a. Read a => ReadPrec (List a)
forall a. Read a => Int -> ReadS (List a)
forall a. Read a => ReadS [List a]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [List a]
$creadListPrec :: forall a. Read a => ReadPrec [List a]
readPrec :: ReadPrec (List a)
$creadPrec :: forall a. Read a => ReadPrec (List a)
readList :: ReadS [List a]
$creadList :: forall a. Read a => ReadS [List a]
readsPrec :: Int -> ReadS (List a)
$creadsPrec :: forall a. Read a => Int -> ReadS (List a)
Read,List a -> List a -> Bool
(List a -> List a -> Bool)
-> (List a -> List a -> Bool) -> Eq (List a)
forall a. Eq a => List a -> List a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: List a -> List a -> Bool
$c/= :: forall a. Eq a => List a -> List a -> Bool
== :: List a -> List a -> Bool
$c== :: forall a. Eq a => List a -> List a -> Bool
Eq,Eq (List a)
Eq (List a)
-> (List a -> List a -> Ordering)
-> (List a -> List a -> Bool)
-> (List a -> List a -> Bool)
-> (List a -> List a -> Bool)
-> (List a -> List a -> Bool)
-> (List a -> List a -> List a)
-> (List a -> List a -> List a)
-> Ord (List a)
List a -> List a -> Bool
List a -> List a -> Ordering
List a -> List a -> List a
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall a. Ord a => Eq (List a)
forall a. Ord a => List a -> List a -> Bool
forall a. Ord a => List a -> List a -> Ordering
forall a. Ord a => List a -> List a -> List a
min :: List a -> List a -> List a
$cmin :: forall a. Ord a => List a -> List a -> List a
max :: List a -> List a -> List a
$cmax :: forall a. Ord a => List a -> List a -> List a
>= :: List a -> List a -> Bool
$c>= :: forall a. Ord a => List a -> List a -> Bool
> :: List a -> List a -> Bool
$c> :: forall a. Ord a => List a -> List a -> Bool
<= :: List a -> List a -> Bool
$c<= :: forall a. Ord a => List a -> List a -> Bool
< :: List a -> List a -> Bool
$c< :: forall a. Ord a => List a -> List a -> Bool
compare :: List a -> List a -> Ordering
$ccompare :: forall a. Ord a => List a -> List a -> Ordering
$cp1Ord :: forall a. Ord a => Eq (List a)
Ord,b -> List a -> List a
NonEmpty (List a) -> List a
List a -> List a -> List a
(List a -> List a -> List a)
-> (NonEmpty (List a) -> List a)
-> (forall b. Integral b => b -> List a -> List a)
-> Semigroup (List a)
forall b. Integral b => b -> List a -> List a
forall a. NonEmpty (List a) -> List a
forall a. List a -> List a -> List a
forall a.
(a -> a -> a)
-> (NonEmpty a -> a)
-> (forall b. Integral b => b -> a -> a)
-> Semigroup a
forall a b. Integral b => b -> List a -> List a
stimes :: b -> List a -> List a
$cstimes :: forall a b. Integral b => b -> List a -> List a
sconcat :: NonEmpty (List a) -> List a
$csconcat :: forall a. NonEmpty (List a) -> List a
<> :: List a -> List a -> List a
$c<> :: forall a. List a -> List a -> List a
Semigroup,Semigroup (List a)
List a
Semigroup (List a)
-> List a
-> (List a -> List a -> List a)
-> ([List a] -> List a)
-> Monoid (List a)
[List a] -> List a
List a -> List a -> List a
forall a. Semigroup (List a)
forall a. List a
forall a.
Semigroup a -> a -> (a -> a -> a) -> ([a] -> a) -> Monoid a
forall a. [List a] -> List a
forall a. List a -> List a -> List a
mconcat :: [List a] -> List a
$cmconcat :: forall a. [List a] -> List a
mappend :: List a -> List a -> List a
$cmappend :: forall a. List a -> List a -> List a
mempty :: List a
$cmempty :: forall a. List a
$cp1Monoid :: forall a. Semigroup (List a)
Monoid,a -> List b -> List a
(a -> b) -> List a -> List b
(forall a b. (a -> b) -> List a -> List b)
-> (forall a b. a -> List b -> List a) -> Functor List
forall a b. a -> List b -> List a
forall a b. (a -> b) -> List a -> List b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: a -> List b -> List a
$c<$ :: forall a b. a -> List b -> List a
fmap :: (a -> b) -> List a -> List b
$cfmap :: forall a b. (a -> b) -> List a -> List b
Functor,a -> List a -> Bool
List m -> m
List a -> [a]
List a -> Bool
List a -> Int
List a -> a
List a -> a
List a -> a
List a -> a
(a -> m) -> List a -> m
(a -> m) -> List a -> m
(a -> b -> b) -> b -> List a -> b
(a -> b -> b) -> b -> List a -> b
(b -> a -> b) -> b -> List a -> b
(b -> a -> b) -> b -> List a -> b
(a -> a -> a) -> List a -> a
(a -> a -> a) -> List a -> a
(forall m. Monoid m => List m -> m)
-> (forall m a. Monoid m => (a -> m) -> List a -> m)
-> (forall m a. Monoid m => (a -> m) -> List a -> m)
-> (forall a b. (a -> b -> b) -> b -> List a -> b)
-> (forall a b. (a -> b -> b) -> b -> List a -> b)
-> (forall b a. (b -> a -> b) -> b -> List a -> b)
-> (forall b a. (b -> a -> b) -> b -> List a -> b)
-> (forall a. (a -> a -> a) -> List a -> a)
-> (forall a. (a -> a -> a) -> List a -> a)
-> (forall a. List a -> [a])
-> (forall a. List a -> Bool)
-> (forall a. List a -> Int)
-> (forall a. Eq a => a -> List a -> Bool)
-> (forall a. Ord a => List a -> a)
-> (forall a. Ord a => List a -> a)
-> (forall a. Num a => List a -> a)
-> (forall a. Num a => List a -> a)
-> Foldable List
forall a. Eq a => a -> List a -> Bool
forall a. Num a => List a -> a
forall a. Ord a => List a -> a
forall m. Monoid m => List m -> m
forall a. List a -> Bool
forall a. List a -> Int
forall a. List a -> [a]
forall a. (a -> a -> a) -> List a -> a
forall m a. Monoid m => (a -> m) -> List a -> m
forall b a. (b -> a -> b) -> b -> List a -> b
forall a b. (a -> b -> b) -> b -> List a -> b
forall (t :: * -> *).
(forall m. Monoid m => t m -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. t a -> [a])
-> (forall a. t a -> Bool)
-> (forall a. t a -> Int)
-> (forall a. Eq a => a -> t a -> Bool)
-> (forall a. Ord a => t a -> a)
-> (forall a. Ord a => t a -> a)
-> (forall a. Num a => t a -> a)
-> (forall a. Num a => t a -> a)
-> Foldable t
product :: List a -> a
$cproduct :: forall a. Num a => List a -> a
sum :: List a -> a
$csum :: forall a. Num a => List a -> a
minimum :: List a -> a
$cminimum :: forall a. Ord a => List a -> a
maximum :: List a -> a
$cmaximum :: forall a. Ord a => List a -> a
elem :: a -> List a -> Bool
$celem :: forall a. Eq a => a -> List a -> Bool
length :: List a -> Int
$clength :: forall a. List a -> Int
null :: List a -> Bool
$cnull :: forall a. List a -> Bool
toList :: List a -> [a]
$ctoList :: forall a. List a -> [a]
foldl1 :: (a -> a -> a) -> List a -> a
$cfoldl1 :: forall a. (a -> a -> a) -> List a -> a
foldr1 :: (a -> a -> a) -> List a -> a
$cfoldr1 :: forall a. (a -> a -> a) -> List a -> a
foldl' :: (b -> a -> b) -> b -> List a -> b
$cfoldl' :: forall b a. (b -> a -> b) -> b -> List a -> b
foldl :: (b -> a -> b) -> b -> List a -> b
$cfoldl :: forall b a. (b -> a -> b) -> b -> List a -> b
foldr' :: (a -> b -> b) -> b -> List a -> b
$cfoldr' :: forall a b. (a -> b -> b) -> b -> List a -> b
foldr :: (a -> b -> b) -> b -> List a -> b
$cfoldr :: forall a b. (a -> b -> b) -> b -> List a -> b
foldMap' :: (a -> m) -> List a -> m
$cfoldMap' :: forall m a. Monoid m => (a -> m) -> List a -> m
foldMap :: (a -> m) -> List a -> m
$cfoldMap :: forall m a. Monoid m => (a -> m) -> List a -> m
fold :: List m -> m
$cfold :: forall m. Monoid m => List m -> m
Foldable)

instance NFData a => NFData (List a)

instance (ToJSON a) => ToJSON (List a) where
  toJSON :: List a -> Value
toJSON (List [a]
ls) = [a] -> Value
forall a. ToJSON a => a -> Value
toJSON [a]
ls

instance (FromJSON a) => FromJSON (List a) where
  parseJSON :: Value -> Parser (List a)
parseJSON Value
Null = List a -> Parser (List a)
forall (m :: * -> *) a. Monad m => a -> m a
return ([a] -> List a
forall a. [a] -> List a
List [])
  parseJSON Value
v      = [a] -> List a
forall a. [a] -> List a
List ([a] -> List a) -> Parser [a] -> Parser (List a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser [a]
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v

data Empty = Empty deriving (Empty -> Empty -> Bool
(Empty -> Empty -> Bool) -> (Empty -> Empty -> Bool) -> Eq Empty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Empty -> Empty -> Bool
$c/= :: Empty -> Empty -> Bool
== :: Empty -> Empty -> Bool
$c== :: Empty -> Empty -> Bool
Eq,Eq Empty
Eq Empty
-> (Empty -> Empty -> Ordering)
-> (Empty -> Empty -> Bool)
-> (Empty -> Empty -> Bool)
-> (Empty -> Empty -> Bool)
-> (Empty -> Empty -> Bool)
-> (Empty -> Empty -> Empty)
-> (Empty -> Empty -> Empty)
-> Ord Empty
Empty -> Empty -> Bool
Empty -> Empty -> Ordering
Empty -> Empty -> Empty
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Empty -> Empty -> Empty
$cmin :: Empty -> Empty -> Empty
max :: Empty -> Empty -> Empty
$cmax :: Empty -> Empty -> Empty
>= :: Empty -> Empty -> Bool
$c>= :: Empty -> Empty -> Bool
> :: Empty -> Empty -> Bool
$c> :: Empty -> Empty -> Bool
<= :: Empty -> Empty -> Bool
$c<= :: Empty -> Empty -> Bool
< :: Empty -> Empty -> Bool
$c< :: Empty -> Empty -> Bool
compare :: Empty -> Empty -> Ordering
$ccompare :: Empty -> Empty -> Ordering
$cp1Ord :: Eq Empty
Ord,Int -> Empty -> ShowS
[Empty] -> ShowS
Empty -> String
(Int -> Empty -> ShowS)
-> (Empty -> String) -> ([Empty] -> ShowS) -> Show Empty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Empty] -> ShowS
$cshowList :: [Empty] -> ShowS
show :: Empty -> String
$cshow :: Empty -> String
showsPrec :: Int -> Empty -> ShowS
$cshowsPrec :: Int -> Empty -> ShowS
Show)
instance ToJSON Empty where
  toJSON :: Empty -> Value
toJSON Empty
Empty = Value
Null
instance FromJSON Empty where
  parseJSON :: Value -> Parser Empty
parseJSON Value
Null = Empty -> Parser Empty
forall (f :: * -> *) a. Applicative f => a -> f a
pure Empty
Empty
  parseJSON (Object Object
o) | Object
o Object -> Object -> Bool
forall a. Eq a => a -> a -> Bool
== Object
forall a. Monoid a => a
mempty = Empty -> Parser Empty
forall (f :: * -> *) a. Applicative f => a -> f a
pure Empty
Empty
  parseJSON Value
_ = String -> Parser Empty
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"expected 'null' or '{}'"