Safe Haskell | None |
---|---|
Language | Haskell2010 |
Benchmarks for these functions can be found at http://code.haskell.org/~aavogt/HList-nodup/Run.html.
See Data-HList-CommonMain.html#v:hSort for the public interface.
Synopsis
- data HLeFn
- data HDown a
- data HNeq le
- class HEqByFn le => HIsAscList le (xs :: [*]) (b :: Bool) | le xs -> b
- class (SameLength a b, HEqByFn le) => HSortBy le (a :: [*]) (b :: [*]) | le a -> b where
- type HSort x y = HSortBy HLeFn x y
- hSort :: HSort x y => HList x -> HList y
- class HSortBy1 ok le (a :: [*]) (b :: [*]) | ok le a -> b where
- class HEqByFn le => HMSortBy le (a :: [*]) (b :: [*]) | le a -> b where
- class HSort2 b x y ab | b x y -> ab where
- class HMerge le x y xy | le x y -> xy where
- type HMerge1 b x y min max = (HCond b (HList x) (HList y) (HList min), HCond b (HList y) (HList x) (HList max))
- hMerge1 :: forall (t :: Bool) y x a b. (HCond t y x a, HCond t x y b) => Proxy t -> y -> x -> (a, b)
- class HQSortBy le (a :: [*]) (b :: [*]) | le a -> b where
- class HEqByFn lt => HSetBy lt (ps :: [*])
- class HSetBy (HNeq HLeFn) ps => HSet (ps :: [*])
- class HIsSet (ps :: [*]) (b :: Bool) | ps -> b
- class HEqByFn lt => HIsSetBy lt (ps :: [*]) (b :: Bool) | lt ps -> b
- class HEqByFn le => HAscList le (ps :: [*])
- class HEqByFn le => HAscList0 le (ps :: [*]) (ps0 :: [*])
- class HEqByFn le => HAscList1 le (b :: Bool) (ps :: [*]) (ps0 :: [*])
Documentation
the "standard" <=
for types. Reuses HEqBy
Note that ghc-7.6 is missing instances for Symbol and Nat, so that
sorting only works HNat
(as used by Data.HList.Label3).
Instances
HEqByFn HLeFn Source # | |
Defined in Data.HList.HSort | |
(x <=? y) ~ b => HEqBy HLeFn (x :: Nat) (y :: Nat) b Source # | only in ghc >= 7.7 |
Defined in Data.HList.HSort | |
(HEq (CmpSymbol x y) 'GT nb, HNot nb ~ b) => HEqBy HLeFn (x :: Symbol) (y :: Symbol) b Source # | only in ghc >= 7.7
|
Defined in Data.HList.HSort | |
HLe x y ~ b => HEqBy HLeFn (x :: HNat) (y :: HNat) b Source # | |
Defined in Data.HList.HSort | |
HEqBy HLeFn x y b => HEqBy HLeFn (Proxy x :: Type) (Proxy y :: Type) b Source # | |
Defined in Data.HList.HSort | |
HEqBy HLeFn x y b => HEqBy HLeFn (Label x :: Type) (Label y :: Type) b Source # | |
Defined in Data.HList.HSort | |
HEqBy HLeFn x y b => HEqBy HLeFn (Tagged x v :: Type) (Tagged y w :: Type) b Source # | |
Defined in Data.HList.HSort | |
(HEqBy HLeFn n m b, ns ~ ns') => HEqBy HLeFn (Lbl n ns desc :: Type) (Lbl m ns' desc' :: Type) b Source # | Data.HList.Label3 labels can only be compared if they belong to the same namespace. |
Defined in Data.HList.HSort |
analogous to Down
The HEqBy instances for HNeq HLeFn
gives <
class HEqByFn le => HIsAscList le (xs :: [*]) (b :: Bool) | le xs -> b Source #
HIsAscList le xs b
is analogous to
b = all (\(x,y) -> x `le` y) (xs `zip` tail xs)
Instances
HEqByFn le => HIsAscList (le :: k) ('[] :: [Type]) 'True Source # | |
Defined in Data.HList.HSort | |
(HEqBy le x y b1, HIsAscList le (y ': ys) b2, HAnd b1 b2 ~ b3) => HIsAscList (le :: k) (x ': (y ': ys)) b3 Source # | |
Defined in Data.HList.HSort | |
HEqByFn le => HIsAscList (le :: k) '[x] 'True Source # | |
Defined in Data.HList.HSort |
class (SameLength a b, HEqByFn le) => HSortBy le (a :: [*]) (b :: [*]) | le a -> b where Source #
quick sort with a special case for sorted lists
Instances
(SameLength a b, HIsAscList le a ok, HSortBy1 ok le a b, HEqByFn le) => HSortBy (le :: k) a b Source # | |
Merge Sort
class HEqByFn le => HMSortBy le (a :: [*]) (b :: [*]) | le a -> b where Source #
HMSortBy is roughly a transcription of this merge sort
msort [] = [] msort [x] = [x] msort [x,y] = hSort2 x y msort xs = case splitAt (length xs `div` 2) xs of (a,b) -> msort a `merge` msort b
hSort2 x y | x <= y = [x,y] | otherwise = [y,x]
merge (x : xs) (y : ys) | x > y = y : merge (x : xs) ys | otherwise = x : merge xs (y : ys)
Instances
HEqByFn le => HMSortBy (le :: k) ('[] :: [Type]) ('[] :: [Type]) Source # | |
(HSort2 b x y ab, HEqBy le x y b, HEqByFn le) => HMSortBy (le :: k) '[x, y] ab Source # | |
(HMerge le xs' ys' sorted, HMSortBy le ys ys', HMSortBy le xs xs', HLengthEq (a ': (b ': (c ': cs))) n2, HDiv2 n2 ~ n, HSplitAt n (a ': (b ': (c ': cs))) xs ys) => HMSortBy (le :: k) (a ': (b ': (c ': cs))) sorted Source # | |
HEqByFn le => HMSortBy (le :: k) '[x] '[x] Source # | |
class HMerge le x y xy | le x y -> xy where Source #
Instances
HMerge (le :: k) ('[] :: [Type]) ('[] :: [Type]) ('[] :: [Type]) Source # | |
HMerge (le :: k) ('[] :: [Type]) (x ': xs) (x ': xs) Source # | |
HMerge (le :: k) (x ': xs) ('[] :: [Type]) (x ': xs) Source # | |
(HEqBy le x y b, HMerge1 b (x ': xs) (y ': ys) (l ': ls) hhs, HMerge le ls hhs srt) => HMerge (le :: k) (x ': xs) (y ': ys) (l ': srt) Source # | |
type HMerge1 b x y min max = (HCond b (HList x) (HList y) (HList min), HCond b (HList y) (HList x) (HList max)) Source #
hMerge1 :: forall (t :: Bool) y x a b. (HCond t y x a, HCond t x y b) => Proxy t -> y -> x -> (a, b) Source #
Quick sort
class HQSortBy le (a :: [*]) (b :: [*]) | le a -> b where Source #
HQSortBy is this algorithm
qsort (x : xs @ (_ : _)) = case partition (<= x) xs of (le, gt) -> qsort le ++ x : qsort gt qsort xs = xs
on random inputs that are not pathological (ie. not already sorted or reverse sorted) this turns out to be faster than HMSortBy, so it is used by default.
Instances
HQSortBy (le :: k) ('[] :: [Type]) ('[] :: [Type]) Source # | |
(HPartitionEq le a (b ': bs) bGeq bLt, HQSortBy le bLt sortedLt, HQSortBy le bGeq sortedGeq, HAppendListR sortedLt (a ': sortedGeq) ~ sorted, HAppendList sortedLt (a ': sortedGeq)) => HQSortBy (le :: k) (a ': (b ': bs)) sorted Source # | |
HQSortBy (le :: k) '[x] '[x] Source # | |
More efficient HRLabelSet / HLabelSet
class HEqByFn lt => HSetBy lt (ps :: [*]) Source #
Provided the labels involved have an appropriate instance of HEqByFn, it would be possible to use the following definitions:
type HRLabelSet = HSet type HLabelSet = HSet
class HIsSet (ps :: [*]) (b :: Bool) | ps -> b Source #
>>>
let xx = Proxy :: HIsSet [Label "x", Label "x"] b => Proxy b
>>>
:t xx
xx :: Proxy 'False
>>>
let xy = Proxy :: HIsSet [Label "x", Label "y"] b => Proxy b
>>>
:t xy
xy :: Proxy 'True
class HEqByFn lt => HIsSetBy lt (ps :: [*]) (b :: Bool) | lt ps -> b Source #
Instances
(HEqByFn lt, HSortBy lt ps ps', HIsAscList lt ps' b) => HIsSetBy (lt :: k) ps b Source # | |
Defined in Data.HList.HSort |
class HEqByFn le => HAscList le (ps :: [*]) Source #
HAscList le xs
confirms that xs is in ascending order,
and reports which element is duplicated otherwise.
>>>
import Data.HList.TypeEqO