{-# LANGUAGE CPP #-}
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE TupleSections #-}
{-# LANGUAGE RoleAnnotations #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE DefaultSignatures #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE MonoLocalBinds #-}
{-# OPTIONS_GHC -fno-cse -fno-full-laziness #-}
module Data.Discrimination.Sorting
( Sort(..)
, Sorting(..)
, Sorting1(..)
, sort, sortWith, desc
, sortingCompare
, toMap
, toMapWith
, toMapWithKey
, toIntMap
, toIntMapWith
, toIntMapWithKey
, toSet
, toIntSet
, sortingNat
, sortingBag
, sortingSet
) where
import Control.Applicative
import Control.Arrow
import Control.Monad
import Data.Bits
import Data.Discrimination.Grouping
import Data.Discrimination.Internal
import Data.Foldable as Foldable hiding (concat)
import Data.Functor.Compose
import Data.Functor.Contravariant
import Data.Functor.Contravariant.Divisible
import Data.Functor.Contravariant.Generic
import Data.Int
import Data.IntMap.Lazy as IntMap
import Data.IntSet as IntSet
import qualified Data.List as List
import Data.Map as Map
import Data.Proxy
import Data.Semigroup hiding (Any)
import Data.Set as Set
import Data.Typeable
import Data.Void
import Data.Word
import Numeric.Natural
import Prelude hiding (read, concat)
newtype Sort a = Sort { runSort :: forall b. [(a,b)] -> [[b]] }
deriving Typeable
mkSort :: (forall b. [(a, b)] -> [[b]]) -> Sort a
mkSort f = Sort $ \xs -> case xs of
[] -> []
[(_, v)] -> [[v]]
_ -> f xs
#ifndef HLINT
type role Sort representational
#endif
instance Contravariant Sort where
contramap f (Sort g) = Sort $ g . fmap (first f)
instance Divisible Sort where
conquer = mkSort $ return . fmap snd
divide k (Sort l) (Sort r) = Sort $ \xs ->
l [ (b, (c, d)) | (a,d) <- xs, let (b, c) = k a] >>= r
instance Decidable Sort where
lose k = Sort $ fmap (absurd.k.fst)
choose f (Sort l) (Sort r) = mkSort $ \xs -> let
ys = fmap (first f) xs
in l [ (k,v) | (Left k, v) <- ys]
++ r [ (k,v) | (Right k, v) <- ys]
instance Semigroup (Sort a) where
Sort l <> Sort r = Sort $ \xs -> l [ (fst x, x) | x <- xs ] >>= r
instance Monoid (Sort a) where
mempty = conquer
mappend = (<>)
class Grouping a => Sorting a where
sorting :: Sort a
#ifndef HLINT
default sorting :: Deciding Sorting a => Sort a
sorting = deciding (Proxy :: Proxy Sorting) sorting
#endif
instance Sorting () where
sorting = conquer
instance Sorting Integer where
sorting = contramap word8s sorting
instance Sorting Natural where
sorting = contramap toInteger sorting
instance Sorting Word8 where
sorting = contramap fromIntegral (sortingNat 256)
instance Sorting Word16 where
sorting = contramap fromIntegral (sortingNat 65536)
instance Sorting Word32 where
sorting = Sort (runs <=< runSort (sortingNat 65536) . join . runSort (sortingNat 65536) . fmap radices) where
radices (x,b) = (fromIntegral x .&. 0xffff, (fromIntegral (unsafeShiftR x 16), (x,b)))
instance Sorting Word64 where
sorting = Sort (runs <=< runSort (sortingNat 65536) . join . runSort (sortingNat 65536) . join
. runSort (sortingNat 65536) . join . runSort (sortingNat 65536) . fmap radices)
where
radices (x,b) = (fromIntegral x .&. 0xffff, (fromIntegral (unsafeShiftR x 16) .&. 0xffff
, (fromIntegral (unsafeShiftR x 32) .&. 0xffff, (fromIntegral (unsafeShiftR x 48)
, (x,b)))))
instance Sorting Word where
sorting
| (maxBound :: Word) == 4294967295 = contramap (fromIntegral :: Word -> Word32) sorting
| otherwise = contramap (fromIntegral :: Word -> Word64) sorting
instance Sorting Int8 where
sorting = contramap (\x -> fromIntegral (x - minBound)) (sortingNat 256)
instance Sorting Int16 where
sorting = contramap (\x -> fromIntegral (x - minBound)) (sortingNat 65536)
instance Sorting Int32 where
sorting = contramap (\x -> fromIntegral (x - minBound) :: Word32) sorting
instance Sorting Int64 where
sorting = contramap (\x -> fromIntegral (x - minBound) :: Word64) sorting
instance Sorting Int where
sorting = contramap (\x -> fromIntegral (x - minBound) :: Word) sorting
instance Sorting Char where
sorting = Sort (runs <=< runSort (sortingNat 1087) . join . runSort (sortingNat 1024) . fmap radices) where
radices (c,b) = (x .&. 0x3ff, (unsafeShiftR x 10, (x,b))) where
x = fromEnum c
instance Sorting Void
instance Sorting Bool
instance Sorting a => Sorting [a]
instance Sorting a => Sorting (Maybe a)
instance (Sorting a, Sorting b) => Sorting (Either a b)
instance (Sorting a, Sorting b) => Sorting (a, b)
instance (Sorting a, Sorting b, Sorting c) => Sorting (a, b, c)
instance (Sorting a, Sorting b, Sorting c, Sorting d) => Sorting (a, b, c, d)
instance (Sorting1 f, Sorting1 g, Sorting a) => Sorting (Compose f g a) where
sorting = getCompose `contramap` sorting1 (sorting1 sorting)
class Grouping1 f => Sorting1 f where
sorting1 :: Sort a -> Sort (f a)
#ifndef HLINT
default sorting1 :: Deciding1 Sorting f => Sort a -> Sort (f a)
sorting1 = deciding1 (Proxy :: Proxy Sorting) sorting
#endif
instance (Sorting1 f, Sorting1 g) => Sorting1 (Compose f g) where
sorting1 f = getCompose `contramap` sorting1 (sorting1 f)
instance Sorting1 []
instance Sorting1 Maybe
instance Sorting a => Sorting1 (Either a)
sortingCompare :: Sorting a => a -> a -> Ordering
sortingCompare a b = case runSort sorting [(a,LT),(b,GT)] of
[r]:_ -> r
_ -> EQ
{-# INLINE sortingCompare #-}
sortingNat :: Int -> Sort Int
sortingNat n = mkSort $ \xs -> List.filter (not . List.null) (bdiscNat n upd xs) where
upd vs v = v : vs
{-# INLINE sortingNat #-}
sortingBag :: Foldable f => Sort k -> Sort (f k)
sortingBag = sortingColl updateBag
sortingSet :: Foldable f => Sort k -> Sort (f k)
sortingSet = sortingColl updateSet
sortingColl :: Foldable f => ([Int] -> Int -> [Int]) -> Sort k -> Sort (f k)
sortingColl upd r = Sort $ \xss -> let
(kss, vs) = unzip xss
elemKeyNumAssocs = groupNum (Foldable.toList <$> kss)
keyNumBlocks = runSort r elemKeyNumAssocs
keyNumElemNumAssocs = groupNum keyNumBlocks
sigs = bdiscNat (length kss) upd keyNumElemNumAssocs
yss = zip sigs vs
in List.filter (not . List.null) $ sorting1 (sortingNat (length keyNumBlocks)) `runSort` yss
desc :: Sort a -> Sort a
desc (Sort l) = Sort (reverse . l)
sort :: Sorting a => [a] -> [a]
sort as = List.concat $ runSort sorting [ (a,a) | a <- as ]
sortWith :: Sorting b => (a -> b) -> [a] -> [a]
sortWith f as = List.concat $ runSort sorting [ (f a, a) | a <- as ]
toMap :: Sorting k => [(k, v)] -> Map k v
toMap kvs = Map.fromDistinctAscList $ last <$> runSort sorting [ (fst kv, kv) | kv <- kvs ]
toMapWith :: Sorting k => (v -> v -> v) -> [(k, v)] -> Map k v
toMapWith f kvs0 = Map.fromDistinctAscList $ go <$> runSort sorting [ (fst kv, kv) | kv <- kvs0 ] where
go ((k,v):kvs) = (k, Prelude.foldl (flip (f . snd)) v kvs)
go [] = error "bad sort"
toMapWithKey :: Sorting k => (k -> v -> v -> v) -> [(k, v)] -> Map k v
toMapWithKey f kvs0 = Map.fromDistinctAscList $ go <$> runSort sorting [ (fst kv, kv) | kv <- kvs0 ] where
go ((k,v):kvs) = (k, Prelude.foldl (flip (f k . snd)) v kvs)
go [] = error "bad sort"
toIntMap :: [(Int, v)] -> IntMap v
toIntMap kvs = IntMap.fromDistinctAscList $ last <$> runSort sorting [ (fst kv, kv) | kv <- kvs ]
toIntMapWith :: (v -> v -> v) -> [(Int, v)] -> IntMap v
toIntMapWith f kvs0 = IntMap.fromDistinctAscList $ go <$> runSort sorting [ (fst kv, kv) | kv <- kvs0 ] where
go ((k,v):kvs) = (k, Prelude.foldl (flip (f . snd)) v kvs)
go [] = error "bad sort"
toIntMapWithKey :: (Int -> v -> v -> v) -> [(Int, v)] -> IntMap v
toIntMapWithKey f kvs0 = IntMap.fromDistinctAscList $ go <$> runSort sorting [ (fst kv, kv) | kv <- kvs0 ] where
go ((k,v):kvs) = (k, Prelude.foldl (flip (f k . snd)) v kvs)
go [] = error "bad sort"
toSet :: Sorting k => [k] -> Set k
toSet kvs = Set.fromDistinctAscList $ last <$> runSort sorting [ (kv, kv) | kv <- kvs ]
toIntSet :: [Int] -> IntSet
toIntSet kvs = IntSet.fromDistinctAscList $ last <$> runSort sorting [ (kv, kv) | kv <- kvs ]