File: Util.hs

package info (click to toggle)
haskell-ordered-containers 0.2.4-1
  • links: PTS, VCS
  • area: main
  • in suites: forky, sid, trixie
  • size: 92 kB
  • sloc: haskell: 434; makefile: 3
file content (59 lines) | stat: -rw-r--r-- 1,895 bytes parent folder | download
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
{-# LANGUAGE CPP #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveFoldable #-}
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE DeriveTraversable #-}
{-# LANGUAGE KindSignatures #-}

module Data.Map.Util where

import Data.Data (Data, Typeable)
import Data.Map (Map)
import Data.Monoid -- so that the docs for Monoid link to the right place
import qualified Data.Map as M

#if !(MIN_VERSION_base(4,8,0))
import Data.Foldable (Foldable)
import Data.Traversable (Traversable)
#endif

-- | An internal index used to track ordering only -- its magnitude doesn't
-- matter. If you manage to see this documentation, the library author has made
-- a mistake!
type Tag = Int

-- | A 0-based index, much like the indices used by lists' '!!' operation. All
-- indices are with respect to insertion order.
type Index = Int

nextLowerTag, nextHigherTag :: Map Tag a -> Tag
nextLowerTag  = maybe 0 pred . minTag
nextHigherTag = maybe 0 succ . maxTag

minTag, maxTag :: Map Tag a -> Maybe Tag
minTag m = fmap (fst . fst) (M.minViewWithKey m)
maxTag m = fmap (fst . fst) (M.maxViewWithKey m)

showsPrecList :: Show a => (b -> [a]) -> Int -> b -> ShowS
showsPrecList toList d o = showParen (d > 10) $
	showString "fromList " . shows (toList o)

readsPrecList :: Read a => ([a] -> b) -> Int -> ReadS b
readsPrecList fromList d = readParen (d > 10) $ \r -> do
	("fromList", s) <- lex r
	(xs, t) <- reads s
	return (fromList xs, t)

-- | A newtype to hang a 'Monoid' instance on. The phantom first parameter
-- tells whether 'mappend' will prefer the indices of its first or second
-- argument if there are shared elements in both.
--
-- @since 0.2
newtype Bias (dir :: IndexPreference) a = Bias { unbiased :: a }
	deriving (Data, Eq, Foldable, Functor, Ord, Read, Show, Traversable, Typeable)
-- | @since 0.2
data IndexPreference = L | R
	deriving Typeable
type L = 'L
type R = 'R