module BNFC.Utils.Singleton where
import Prelude (id, (.), uncurry, (++), map, Maybe(..), Monoid(..), Ord)
import Data.Semigroup (Semigroup)
import Data.List.NonEmpty (NonEmpty(..))
import Data.Map (Map)
import Data.Set (Set)
import qualified Data.Map as Map
import qualified Data.Set as Set
class (Semigroup coll, Monoid coll, Singleton el coll) => Collection el coll
| coll -> el where
fromList :: [el] -> coll
fromList = [coll] -> coll
forall a. Monoid a => [a] -> a
mconcat ([coll] -> coll) -> ([el] -> [coll]) -> [el] -> coll
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (el -> coll) -> [el] -> [coll]
forall a b. (a -> b) -> [a] -> [b]
map el -> coll
forall el coll. Singleton el coll => el -> coll
singleton
instance Collection a [a] where fromList :: [a] -> [a]
fromList = [a] -> [a]
forall a. a -> a
id
instance Collection a ([a] -> [a]) where fromList :: [a] -> [a] -> [a]
fromList = [a] -> [a] -> [a]
forall a. [a] -> [a] -> [a]
(++)
instance Ord a => Collection a (Set a) where fromList :: [a] -> Set a
fromList = [a] -> Set a
forall a. Ord a => [a] -> Set a
Set.fromList
instance Ord k => Collection (k, a) (Map k a) where fromList :: [(k, a)] -> Map k a
fromList = [(k, a)] -> Map k a
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList
class Singleton el coll | coll -> el where
singleton :: el -> coll
instance Singleton a (Maybe a) where singleton :: a -> Maybe a
singleton = a -> Maybe a
forall a. a -> Maybe a
Just
instance Singleton a [a] where singleton :: a -> [a]
singleton = (a -> [a] -> [a]
forall a. a -> [a] -> [a]
:[])
instance Singleton a ([a] -> [a]) where singleton :: a -> [a] -> [a]
singleton = (:)
instance Singleton a (NonEmpty a) where singleton :: a -> NonEmpty a
singleton = (a -> [a] -> NonEmpty a
forall a. a -> [a] -> NonEmpty a
:| [])
instance Singleton a (Set a) where singleton :: a -> Set a
singleton = a -> Set a
forall a. a -> Set a
Set.singleton
instance Singleton (k,a) (Map k a) where singleton :: (k, a) -> Map k a
singleton = (k -> a -> Map k a) -> (k, a) -> Map k a
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry k -> a -> Map k a
forall k a. k -> a -> Map k a
Map.singleton