dhall-1.41.2: A configuration language guaranteed to terminate
Safe HaskellNone
LanguageHaskell2010

Dhall.Set

Description

This module only exports ways of constructing a Set, retrieving List, Set, and Seq representations of the same data, as well as a novel "difference" function. Any other Set-like or List-like functionality should be obtained through toSet and toList, respectively.

Synopsis

Documentation

data Set a Source #

This is a variation on Data.Set.Set that remembers the original order of elements. This ensures that ordering is not lost when formatting Dhall code

Constructors

Set (Set a) (Seq a) 

Instances

Instances details
Foldable Set Source # 
Instance details

Defined in Dhall.Set

Methods

fold :: Monoid m => Set m -> m #

foldMap :: Monoid m => (a -> m) -> Set a -> m #

foldMap' :: Monoid m => (a -> m) -> Set a -> m #

foldr :: (a -> b -> b) -> b -> Set a -> b #

foldr' :: (a -> b -> b) -> b -> Set a -> b #

foldl :: (b -> a -> b) -> b -> Set a -> b #

foldl' :: (b -> a -> b) -> b -> Set a -> b #

foldr1 :: (a -> a -> a) -> Set a -> a #

foldl1 :: (a -> a -> a) -> Set a -> a #

toList :: Set a -> [a] #

null :: Set a -> Bool #

length :: Set a -> Int #

elem :: Eq a => a -> Set a -> Bool #

maximum :: Ord a => Set a -> a #

minimum :: Ord a => Set a -> a #

sum :: Num a => Set a -> a #

product :: Num a => Set a -> a #

Lift a => Lift (Set a :: Type) Source # 
Instance details

Defined in Dhall.Set

Methods

lift :: Set a -> Q Exp #

liftTyped :: Set a -> Q (TExp (Set a)) #

Eq a => Eq (Set a) Source # 
Instance details

Defined in Dhall.Set

Methods

(==) :: Set a -> Set a -> Bool #

(/=) :: Set a -> Set a -> Bool #

(Data a, Ord a) => Data (Set a) Source # 
Instance details

Defined in Dhall.Set

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Set a -> c (Set a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Set a) #

toConstr :: Set a -> Constr #

dataTypeOf :: Set a -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Set a)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Set a)) #

gmapT :: (forall b. Data b => b -> b) -> Set a -> Set a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Set a -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Set a -> r #

gmapQ :: (forall d. Data d => d -> u) -> Set a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Set a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Set a -> m (Set a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Set a -> m (Set a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Set a -> m (Set a) #

Ord a => Ord (Set a) Source # 
Instance details

Defined in Dhall.Set

Methods

compare :: Set a -> Set a -> Ordering #

(<) :: Set a -> Set a -> Bool #

(<=) :: Set a -> Set a -> Bool #

(>) :: Set a -> Set a -> Bool #

(>=) :: Set a -> Set a -> Bool #

max :: Set a -> Set a -> Set a #

min :: Set a -> Set a -> Set a #

Show a => Show (Set a) Source # 
Instance details

Defined in Dhall.Set

Methods

showsPrec :: Int -> Set a -> ShowS #

show :: Set a -> String #

showList :: [Set a] -> ShowS #

Generic (Set a) Source # 
Instance details

Defined in Dhall.Set

Associated Types

type Rep (Set a) :: Type -> Type #

Methods

from :: Set a -> Rep (Set a) x #

to :: Rep (Set a) x -> Set a #

NFData a => NFData (Set a) Source # 
Instance details

Defined in Dhall.Set

Methods

rnf :: Set a -> () #

type Rep (Set a) Source # 
Instance details

Defined in Dhall.Set

type Rep (Set a) = D1 ('MetaData "Set" "Dhall.Set" "dhall-1.41.2-CygVEUAXWhKKGHhZSAzzm9" 'False) (C1 ('MetaCons "Set" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Set a)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Seq a))))

toList :: Set a -> [a] Source #

Convert a Set to a list, preserving the original order of the elements

toAscList :: Set a -> [a] Source #

Convert a Set to a list of ascending elements

toSet :: Set a -> Set a Source #

Convert to an unordered Data.Set.Set

toSeq :: Set a -> Seq a Source #

Convert to an ordered Seq

fromList :: Ord a => [a] -> Set a Source #

Convert a list to a Set, remembering the element order

fromSet :: Set a -> Set a Source #

Convert a Data.Set.Set to a sorted Set

append :: Ord a => a -> Set a -> Set a Source #

Append an element to the end of a Set

empty :: Set a Source #

The empty Set

difference :: Ord a => Set a -> Set a -> [a] Source #

Returns, in order, all elements of the first Set not present in the second. (It doesn't matter in what order the elements appear in the second Set.)

sort :: Ord a => Set a -> Set a Source #

Sort the set elements, forgetting their original ordering.

>>> sort (fromList [2, 1]) == fromList [1, 2]
True

isSorted :: Ord a => Set a -> Bool Source #

>>> isSorted (fromList [2, 1])
False
>>> isSorted (fromList [1, 2])
True

null :: Set a -> Bool Source #

>>> null (fromList [1])
False
>>> null (fromList [])
True

size :: Set a -> Int Source #

>>> size (fromList [1])
1