dependent-map-0.4.0.0/0000755000000000000000000000000007346545000012563 5ustar0000000000000000dependent-map-0.4.0.0/ChangeLog.md0000755000000000000000000000134207346545000014737 0ustar0000000000000000# Revision history for dependent-map ## 0.4.0.0 - 2020-03-26 * Stop re-exporting `Some(..)`, `GCompare(..)`, and `GOrdering(..)` from `dependent-sum` (which itself re-exports from `some` in some versions). * Stop re-exporting `DSum(..)` from `dependent-sum`. ## 0.3.1.0 - 2020-03-26 * Drop support for non-GHC compilers. * Drop support for GHC < 8. * Update maintainer and GitHub links. * Support `dependent-sum` 0.7. * Add `ffor`, `fforWithKey`, `forWithKey`, `forWithKey_`, and `traverseWithKey_` to `Data.Dependent.Map`. * Enable `PolyKinds` for `Data.Dependent.Map.Lens`. ## 0.3 - 2019-03-21 * Change instances of Eq, Ord, Read, Show to use Has' from constraints-extras instead of *Tag classes. * This ends support for GHC 7.x. dependent-map-0.4.0.0/LICENSE0000644000000000000000000001063707346545000013577 0ustar0000000000000000This library (dependent-maps) is derived from code from the containers library. I have no idea which, if any, of the following licenses apply, so I've copied them all. Any modifications by myself I release into the public domain, because in my opinion the concept of owning information (ownership being a prerequisite to licensing) is pretty silly in the first place. And, from a practical standpoint, the proliferation of legalese that must be attached to every piece of software of any appreciable size is actually quite obscene already. ----------------------------------------------------------------------------- This library (libraries/containers) is derived from code from several sources: * Code from the GHC project which is largely (c) The University of Glasgow, and distributable under a BSD-style license (see below), * Code from the Haskell 98 Report which is (c) Simon Peyton Jones and freely redistributable (but see the full license for restrictions). * Code from the Haskell Foreign Function Interface specification, which is (c) Manuel M. T. Chakravarty and freely redistributable (but see the full license for restrictions). The full text of these licenses is reproduced below. All of the licenses are BSD-style or compatible. ----------------------------------------------------------------------------- The Glasgow Haskell Compiler License Copyright 2004, The University Court of the University of Glasgow. All rights reserved. Redistribution and use in source and binary forms, with or without modification, are permitted provided that the following conditions are met: - Redistributions of source code must retain the above copyright notice, this list of conditions and the following disclaimer. - Redistributions in binary form must reproduce the above copyright notice, this list of conditions and the following disclaimer in the documentation and/or other materials provided with the distribution. - Neither name of the University nor the names of its contributors may be used to endorse or promote products derived from this software without specific prior written permission. THIS SOFTWARE IS PROVIDED BY THE UNIVERSITY COURT OF THE UNIVERSITY OF GLASGOW AND THE CONTRIBUTORS "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE UNIVERSITY COURT OF THE UNIVERSITY OF GLASGOW OR THE CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. ----------------------------------------------------------------------------- Code derived from the document "Report on the Programming Language Haskell 98", is distributed under the following license: Copyright (c) 2002 Simon Peyton Jones The authors intend this Report to belong to the entire Haskell community, and so we grant permission to copy and distribute it for any purpose, provided that it is reproduced in its entirety, including this Notice. Modified versions of this Report may also be copied and distributed for any purpose, provided that the modified version is clearly presented as such, and that it does not claim to be a definition of the Haskell 98 Language. ----------------------------------------------------------------------------- Code derived from the document "The Haskell 98 Foreign Function Interface, An Addendum to the Haskell 98 Report" is distributed under the following license: Copyright (c) 2002 Manuel M. T. Chakravarty The authors intend this Report to belong to the entire Haskell community, and so we grant permission to copy and distribute it for any purpose, provided that it is reproduced in its entirety, including this Notice. Modified versions of this Report may also be copied and distributed for any purpose, provided that the modified version is clearly presented as such, and that it does not claim to be a definition of the Haskell 98 Foreign Function Interface. ----------------------------------------------------------------------------- dependent-map-0.4.0.0/README.md0000755000000000000000000000326507346545000014053 0ustar0000000000000000dependent-map [![Build Status](https://travis-ci.org/obsidiansystems/dependent-map.svg)](https://travis-ci.org/obsidiansystems/dependent-map) [![Hackage](https://img.shields.io/hackage/v/dependent-map.svg)](http://hackage.haskell.org/package/dependent-map) ============== This library defines a dependently-typed finite map type. It is derived from `Data.Map.Map` in the `containers` package, but rather than (conceptually) storing pairs indexed by the first component, it stores `DSum`s (from the `dependent-sum` package) indexed by tag. For example ```haskell {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE TypeFamilies #-} module Example where import Data.Constraint.Extras.TH (deriveArgDict) import Data.Dependent.Map (DMap, fromList, singleton, union, unionWithKey) import Data.Dependent.Sum ((==>)) import Data.Functor.Identity (Identity(..)) import Data.GADT.Compare.TH (deriveGCompare, deriveGEq) import Data.GADT.Show.TH (deriveGShow) data Tag a where StringKey :: Tag String IntKey :: Tag Int DoubleKey :: Tag Double deriveGEq ''Tag deriveGCompare ''Tag deriveGShow ''Tag deriveArgDict ''Tag x :: DMap Tag Identity x = fromList [DoubleKey ==> pi, StringKey ==> "hello there"] y :: DMap Tag Identity y = singleton IntKey (Identity 42) z :: DMap Tag Identity z = y `union` fromList [DoubleKey ==> -1.1415926535897931] addFoo :: Tag v -> Identity v -> Identity v -> Identity v addFoo IntKey (Identity x) (Identity y) = Identity $ x + y addFoo DoubleKey (Identity x) (Identity y) = Identity $ x + y addFoo _ x _ = x main :: IO () main = mapM_ print [ x, y, z , unionWithKey addFoo x z ] ``` dependent-map-0.4.0.0/Setup.lhs0000644000000000000000000000011607346545000014371 0ustar0000000000000000#!/usr/bin/env runhaskell > import Distribution.Simple > main = defaultMain dependent-map-0.4.0.0/dependent-map.cabal0000644000000000000000000000317107346545000016272 0ustar0000000000000000name: dependent-map version: 0.4.0.0 stability: provisional cabal-version: >= 1.6 build-type: Simple author: James Cook maintainer: Obsidian Systems, LLC license: OtherLicense license-file: LICENSE homepage: https://github.com/obsidiansystems/dependent-map category: Data, Dependent Types synopsis: Dependent finite maps (partial dependent products) description: Provides a type called @DMap@ which generalizes @Data.Map.Map@, allowing keys to specify the type of value that can be associated with them. extra-source-files: ChangeLog.md README.md tested-with: GHC == 8.0.2, GHC == 8.2.2, GHC == 8.4.4, GHC == 8.6.5, GHC == 8.8.3 source-repository head type: git location: https://github.com/obsidiansystems/dependent-map Library hs-source-dirs: src ghc-options: -fwarn-unused-imports -fwarn-unused-binds exposed-modules: Data.Dependent.Map, Data.Dependent.Map.Lens, Data.Dependent.Map.Internal other-modules: Data.Dependent.Map.PtrEquality build-depends: base >= 4.9 && < 5, containers >= 0.5.7.1 && <0.7, dependent-sum >= 0.6.1 && < 0.8, constraints-extras >= 0.2.3.0 && < 0.4 dependent-map-0.4.0.0/src/Data/Dependent/0000755000000000000000000000000007346545000016131 5ustar0000000000000000dependent-map-0.4.0.0/src/Data/Dependent/Map.hs0000644000000000000000000013574107346545000017215 0ustar0000000000000000{-# LANGUAGE CPP #-} {-# LANGUAGE BangPatterns #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE PolyKinds #-} {-# LANGUAGE RankNTypes #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE Trustworthy #-} {-# LANGUAGE TypeApplications #-} {-# LANGUAGE TypeOperators #-} {-# LANGUAGE UndecidableInstances #-} module Data.Dependent.Map ( DMap -- * Operators , (!), (\\) -- * Query , null , size , member , notMember , lookup , findWithDefault -- * Construction , empty , singleton -- ** Insertion , insert , insertWith , insertWith' , insertWithKey , insertWithKey' , insertLookupWithKey , insertLookupWithKey' -- ** Delete\/Update , delete , adjust , adjustWithKey , adjustWithKey' , update , updateWithKey , updateLookupWithKey , alter , alterF -- * Combine -- ** Union , union , unionWithKey , unions , unionsWithKey -- ** Difference , difference , differenceWithKey -- ** Intersection , intersection , intersectionWithKey -- * Traversal -- ** Map , map , ffor , mapWithKey , fforWithKey , traverseWithKey_ , forWithKey_ , traverseWithKey , forWithKey , mapAccumLWithKey , mapAccumRWithKey , mapKeysWith , mapKeysMonotonic -- ** Fold , foldWithKey , foldrWithKey , foldlWithKey -- , foldlWithKey' -- * Conversion , keys , assocs -- ** Lists , toList , fromList , fromListWithKey -- ** Ordered lists , toAscList , toDescList , fromAscList , fromAscListWithKey , fromDistinctAscList -- * Filter , filter , filterWithKey , partitionWithKey , mapMaybe , mapMaybeWithKey , mapEitherWithKey , split , splitLookup -- * Submap , isSubmapOf, isSubmapOfBy , isProperSubmapOf, isProperSubmapOfBy -- * Indexed , lookupIndex , findIndex , elemAt , updateAt , deleteAt -- * Min\/Max , findMin , findMax , lookupMin , lookupMax , deleteMin , deleteMax , deleteFindMin , deleteFindMax , updateMinWithKey , updateMaxWithKey , minViewWithKey , maxViewWithKey -- * Debugging , showTree , showTreeWith , valid ) where import Prelude hiding (null, lookup, map) import qualified Prelude import Data.Constraint.Extras (Has', has') import Data.Dependent.Sum (DSum((:=>))) import Data.GADT.Compare (GCompare, GEq, GOrdering(..), gcompare, geq) import Data.GADT.Show (GRead, GShow) import Data.Maybe (isJust) import Data.Some (Some, mkSome) import Data.Typeable ((:~:)(Refl)) import Text.Read (Lexeme(Ident), lexP, parens, prec, readListPrec, readListPrecDefault, readPrec) #if !MIN_VERSION_base(4,11,0) import Data.Semigroup (Semigroup, (<>)) #endif import Data.Dependent.Map.Internal import Data.Dependent.Map.PtrEquality (ptrEq) instance (GCompare k) => Monoid (DMap k f) where mempty = empty mappend = union mconcat = unions instance (GCompare k) => Semigroup (DMap k f) where (<>) = mappend {-------------------------------------------------------------------- Operators --------------------------------------------------------------------} infixl 9 \\,! -- \\ at the end of the line means line continuation -- | /O(log n)/. Find the value at a key. -- Calls 'error' when the element can not be found. -- -- > fromList [(5,'a'), (3,'b')] ! 1 Error: element not in the map -- > fromList [(5,'a'), (3,'b')] ! 5 == 'a' (!) :: GCompare k => DMap k f -> k v -> f v (!) m k = find k m -- | Same as 'difference'. (\\) :: GCompare k => DMap k f -> DMap k f -> DMap k f m1 \\ m2 = difference m1 m2 -- #if __GLASGOW_HASKELL__ -- -- {-------------------------------------------------------------------- -- A Data instance -- --------------------------------------------------------------------} -- -- -- This instance preserves data abstraction at the cost of inefficiency. -- -- We omit reflection services for the sake of data abstraction. -- -- instance (Data k, Data a, GCompare k) => Data (DMap k) where -- gfoldl f z m = z fromList `f` toList m -- toConstr _ = error "toConstr" -- gunfold _ _ = error "gunfold" -- dataTypeOf _ = mkNoRepType "Data.Map.Map" -- dataCast2 f = gcast2 f -- -- #endif {-------------------------------------------------------------------- Query --------------------------------------------------------------------} -- | /O(log n)/. Is the key a member of the map? See also 'notMember'. member :: GCompare k => k a -> DMap k f -> Bool member k = isJust . lookup k -- | /O(log n)/. Is the key not a member of the map? See also 'member'. notMember :: GCompare k => k v -> DMap k f -> Bool notMember k m = not (member k m) -- | /O(log n)/. Find the value at a key. -- Calls 'error' when the element can not be found. -- Consider using 'lookup' when elements may not be present. find :: GCompare k => k v -> DMap k f -> f v find k m = case lookup k m of Nothing -> error "DMap.find: element not in the map" Just v -> v -- | /O(log n)/. The expression @('findWithDefault' def k map)@ returns -- the value at key @k@ or returns default value @def@ -- when the key is not in the map. findWithDefault :: GCompare k => f v -> k v -> DMap k f -> f v findWithDefault def k m = case lookup k m of Nothing -> def Just v -> v {-------------------------------------------------------------------- Insertion --------------------------------------------------------------------} -- | /O(log n)/. Insert a new key and value in the map. -- If the key is already present in the map, the associated value is -- replaced with the supplied value. 'insert' is equivalent to -- @'insertWith' 'const'@. insert :: forall k f v. GCompare k => k v -> f v -> DMap k f -> DMap k f insert kx x = kx `seq` go where go :: DMap k f -> DMap k f go Tip = singleton kx x go t@(Bin sz ky y l r) = case gcompare kx ky of GLT -> let !l' = go l in if l' `ptrEq` l then t else balance ky y l' r GGT -> let !r' = go r in if r' `ptrEq` r then t else balance ky y l r' GEQ | kx `ptrEq` ky && x `ptrEq` y -> t | otherwise -> Bin sz kx x l r -- | /O(log n)/. Insert a new key and value in the map if the key -- is not already present. If the key is already present, @insertR@ -- does nothing. insertR :: forall k f v. GCompare k => k v -> f v -> DMap k f -> DMap k f insertR kx x = kx `seq` go where go :: DMap k f -> DMap k f go Tip = singleton kx x go t@(Bin sz ky y l r) = case gcompare kx ky of GLT -> let !l' = go l in if l' `ptrEq` l then t else balance ky y l' r GGT -> let !r' = go r in if r' `ptrEq` r then t else balance ky y l r' GEQ -> t -- | /O(log n)/. Insert with a function, combining new value and old value. -- @'insertWith' f key value mp@ -- will insert the entry @key :=> value@ into @mp@ if key does -- not exist in the map. If the key does exist, the function will -- insert the entry @key :=> f new_value old_value@. insertWith :: GCompare k => (f v -> f v -> f v) -> k v -> f v -> DMap k f -> DMap k f insertWith f = insertWithKey (\_ x' y' -> f x' y') -- | Same as 'insertWith', but the combining function is applied strictly. -- This is often the most desirable behavior. insertWith' :: GCompare k => (f v -> f v -> f v) -> k v -> f v -> DMap k f -> DMap k f insertWith' f = insertWithKey' (\_ x' y' -> f x' y') -- | /O(log n)/. Insert with a function, combining key, new value and old value. -- @'insertWithKey' f key value mp@ -- will insert the entry @key :=> value@ into @mp@ if key does -- not exist in the map. If the key does exist, the function will -- insert the entry @key :=> f key new_value old_value@. -- Note that the key passed to f is the same key passed to 'insertWithKey'. insertWithKey :: forall k f v. GCompare k => (k v -> f v -> f v -> f v) -> k v -> f v -> DMap k f -> DMap k f insertWithKey f kx x = kx `seq` go where go :: DMap k f -> DMap k f go Tip = singleton kx x go (Bin sy ky y l r) = case gcompare kx ky of GLT -> balance ky y (go l) r GGT -> balance ky y l (go r) GEQ -> Bin sy kx (f kx x y) l r -- | Same as 'insertWithKey', but the combining function is applied strictly. insertWithKey' :: forall k f v. GCompare k => (k v -> f v -> f v -> f v) -> k v -> f v -> DMap k f -> DMap k f insertWithKey' f kx x = kx `seq` go where go :: DMap k f -> DMap k f go Tip = singleton kx $! x go (Bin sy ky y l r) = case gcompare kx ky of GLT -> balance ky y (go l) r GGT -> balance ky y l (go r) GEQ -> let x' = f kx x y in seq x' (Bin sy kx x' l r) -- | /O(log n)/. Combines insert operation with old value retrieval. -- The expression (@'insertLookupWithKey' f k x map@) -- is a pair where the first element is equal to (@'lookup' k map@) -- and the second element equal to (@'insertWithKey' f k x map@). insertLookupWithKey :: forall k f v. GCompare k => (k v -> f v -> f v -> f v) -> k v -> f v -> DMap k f -> (Maybe (f v), DMap k f) insertLookupWithKey f kx x = kx `seq` go where go :: DMap k f -> (Maybe (f v), DMap k f) go Tip = (Nothing, singleton kx x) go (Bin sy ky y l r) = case gcompare kx ky of GLT -> let (found, l') = go l in (found, balance ky y l' r) GGT -> let (found, r') = go r in (found, balance ky y l r') GEQ -> (Just y, Bin sy kx (f kx x y) l r) -- | /O(log n)/. A strict version of 'insertLookupWithKey'. insertLookupWithKey' :: forall k f v. GCompare k => (k v -> f v -> f v -> f v) -> k v -> f v -> DMap k f -> (Maybe (f v), DMap k f) insertLookupWithKey' f kx x = kx `seq` go where go :: DMap k f -> (Maybe (f v), DMap k f) go Tip = x `seq` (Nothing, singleton kx x) go (Bin sy ky y l r) = case gcompare kx ky of GLT -> let (found, l') = go l in (found, balance ky y l' r) GGT -> let (found, r') = go r in (found, balance ky y l r') GEQ -> let x' = f kx x y in x' `seq` (Just y, Bin sy kx x' l r) {-------------------------------------------------------------------- Deletion [delete] is the inlined version of [deleteWith (\k x -> Nothing)] --------------------------------------------------------------------} -- | /O(log n)/. Delete a key and its value from the map. When the key is not -- a member of the map, the original map is returned. delete :: forall k f v. GCompare k => k v -> DMap k f -> DMap k f delete k = k `seq` go where go :: DMap k f -> DMap k f go Tip = Tip go (Bin _ kx x l r) = case gcompare k kx of GLT -> balance kx x (go l) r GGT -> balance kx x l (go r) GEQ -> glue l r -- | /O(log n)/. Update a value at a specific key with the result of the provided function. -- When the key is not -- a member of the map, the original map is returned. adjust :: GCompare k => (f v -> f v) -> k v -> DMap k f -> DMap k f adjust f = adjustWithKey (\_ x -> f x) -- | /O(log n)/. Adjust a value at a specific key. When the key is not -- a member of the map, the original map is returned. adjustWithKey :: GCompare k => (k v -> f v -> f v) -> k v -> DMap k f -> DMap k f adjustWithKey f0 !k0 = go f0 k0 where go :: GCompare k => (k v -> f v -> f v) -> k v -> DMap k f -> DMap k f go _f _k Tip = Tip go f k (Bin sx kx x l r) = case gcompare k kx of GLT -> Bin sx kx x (go f k l) r GGT -> Bin sx kx x l (go f k r) GEQ -> Bin sx kx (f kx x) l r -- | /O(log n)/. A strict version of 'adjustWithKey'. adjustWithKey' :: GCompare k => (k v -> f v -> f v) -> k v -> DMap k f -> DMap k f adjustWithKey' f0 !k0 = go f0 k0 where go :: GCompare k => (k v -> f v -> f v) -> k v -> DMap k f -> DMap k f go _f _k Tip = Tip go f k (Bin sx kx x l r) = case gcompare k kx of GLT -> Bin sx kx x (go f k l) r GGT -> Bin sx kx x l (go f k r) GEQ -> let !x' = f kx x in Bin sx kx x' l r -- | /O(log n)/. The expression (@'update' f k map@) updates the value @x@ -- at @k@ (if it is in the map). If (@f x@) is 'Nothing', the element is -- deleted. If it is (@'Just' y@), the key @k@ is bound to the new value @y@. update :: GCompare k => (f v -> Maybe (f v)) -> k v -> DMap k f -> DMap k f update f = updateWithKey (\_ x -> f x) -- | /O(log n)/. The expression (@'updateWithKey' f k map@) updates the -- value @x@ at @k@ (if it is in the map). If (@f k x@) is 'Nothing', -- the element is deleted. If it is (@'Just' y@), the key @k@ is bound -- to the new value @y@. updateWithKey :: forall k f v. GCompare k => (k v -> f v -> Maybe (f v)) -> k v -> DMap k f -> DMap k f updateWithKey f k = k `seq` go where go :: DMap k f -> DMap k f go Tip = Tip go (Bin sx kx x l r) = case gcompare k kx of GLT -> balance kx x (go l) r GGT -> balance kx x l (go r) GEQ -> case f kx x of Just x' -> Bin sx kx x' l r Nothing -> glue l r -- | /O(log n)/. Lookup and update. See also 'updateWithKey'. -- The function returns changed value, if it is updated. -- Returns the original key value if the map entry is deleted. updateLookupWithKey :: forall k f v. GCompare k => (k v -> f v -> Maybe (f v)) -> k v -> DMap k f -> (Maybe (f v), DMap k f) updateLookupWithKey f k = k `seq` go where go :: DMap k f -> (Maybe (f v), DMap k f) go Tip = (Nothing,Tip) go (Bin sx kx x l r) = case gcompare k kx of GLT -> let (found,l') = go l in (found,balance kx x l' r) GGT -> let (found,r') = go r in (found,balance kx x l r') GEQ -> case f kx x of Just x' -> (Just x',Bin sx kx x' l r) Nothing -> (Just x,glue l r) -- | /O(log n)/. The expression (@'alter' f k map@) alters the value @x@ at @k@, or absence thereof. -- 'alter' can be used to insert, delete, or update a value in a 'Map'. -- In short : @'lookup' k ('alter' f k m) = f ('lookup' k m)@. alter :: forall k f v. GCompare k => (Maybe (f v) -> Maybe (f v)) -> k v -> DMap k f -> DMap k f alter f k = k `seq` go where go :: DMap k f -> DMap k f go Tip = case f Nothing of Nothing -> Tip Just x -> singleton k x go (Bin sx kx x l r) = case gcompare k kx of GLT -> balance kx x (go l) r GGT -> balance kx x l (go r) GEQ -> case f (Just x) of Just x' -> Bin sx kx x' l r Nothing -> glue l r -- | Works the same as 'alter' except the new value is returned in some 'Functor' @f@. -- In short : @(\v' -> alter (const v') k dm) <$> f (lookup k dm)@ alterF :: forall k f v g. (GCompare k, Functor f) => k v -> (Maybe (g v) -> f (Maybe (g v))) -> DMap k g -> f (DMap k g) alterF k f = go where go :: DMap k g -> f (DMap k g) go Tip = maybe Tip (singleton k) <$> f Nothing go (Bin sx kx x l r) = case gcompare k kx of GLT -> (\l' -> balance kx x l' r) <$> go l GGT -> (\r' -> balance kx x l r') <$> go r GEQ -> maybe (glue l r) (\x' -> Bin sx kx x' l r) <$> f (Just x) {-------------------------------------------------------------------- Indexing --------------------------------------------------------------------} -- | /O(log n)/. Return the /index/ of a key. The index is a number from -- /0/ up to, but not including, the 'size' of the map. Calls 'error' when -- the key is not a 'member' of the map. findIndex :: GCompare k => k v -> DMap k f -> Int findIndex k t = case lookupIndex k t of Nothing -> error "Map.findIndex: element is not in the map" Just idx -> idx -- | /O(log n)/. Lookup the /index/ of a key. The index is a number from -- /0/ up to, but not including, the 'size' of the map. lookupIndex :: forall k f v. GCompare k => k v -> DMap k f -> Maybe Int lookupIndex k = k `seq` go 0 where go :: Int -> DMap k f -> Maybe Int go !idx Tip = idx `seq` Nothing go !idx (Bin _ kx _ l r) = case gcompare k kx of GLT -> go idx l GGT -> go (idx + size l + 1) r GEQ -> Just (idx + size l) -- | /O(log n)/. Retrieve an element by /index/. Calls 'error' when an -- invalid index is used. elemAt :: Int -> DMap k f -> DSum k f elemAt _ Tip = error "Map.elemAt: index out of range" elemAt i (Bin _ kx x l r) = case compare i sizeL of LT -> elemAt i l GT -> elemAt (i-sizeL-1) r EQ -> kx :=> x where sizeL = size l -- | /O(log n)/. Update the element at /index/. Does nothing when an -- invalid index is used. updateAt :: (forall v. k v -> f v -> Maybe (f v)) -> Int -> DMap k f -> DMap k f updateAt f i0 t = i0 `seq` go i0 t where go _ Tip = Tip go i (Bin sx kx x l r) = case compare i sizeL of LT -> balance kx x (go i l) r GT -> balance kx x l (go (i-sizeL-1) r) EQ -> case f kx x of Just x' -> Bin sx kx x' l r Nothing -> glue l r where sizeL = size l -- | /O(log n)/. Delete the element at /index/. -- Defined as (@'deleteAt' i map = 'updateAt' (\k x -> 'Nothing') i map@). deleteAt :: Int -> DMap k f -> DMap k f deleteAt i m = updateAt (\_ _ -> Nothing) i m {-------------------------------------------------------------------- Minimal, Maximal --------------------------------------------------------------------} -- | /O(log n)/. The minimal key of the map. Calls 'error' is the map is empty. findMin :: DMap k f -> DSum k f findMin m = case lookupMin m of Just x -> x Nothing -> error "Map.findMin: empty map has no minimal element" lookupMin :: DMap k f -> Maybe (DSum k f) lookupMin m = case m of Tip -> Nothing Bin _ kx x l _ -> Just $! go kx x l where go :: k v -> f v -> DMap k f -> DSum k f go kx x Tip = kx :=> x go _ _ (Bin _ kx x l _) = go kx x l -- | /O(log n)/. The maximal key of the map. Calls 'error' is the map is empty. findMax :: DMap k f -> DSum k f findMax m = case lookupMax m of Just x -> x Nothing -> error "Map.findMax: empty map has no maximal element" lookupMax :: DMap k f -> Maybe (DSum k f) lookupMax m = case m of Tip -> Nothing Bin _ kx x _ r -> Just $! go kx x r where go :: k v -> f v -> DMap k f -> DSum k f go kx x Tip = kx :=> x go _ _ (Bin _ kx x _ r) = go kx x r -- | /O(log n)/. Delete the minimal key. Returns an empty map if the map is empty. deleteMin :: DMap k f -> DMap k f deleteMin (Bin _ _ _ Tip r) = r deleteMin (Bin _ kx x l r) = balance kx x (deleteMin l) r deleteMin Tip = Tip -- | /O(log n)/. Delete the maximal key. Returns an empty map if the map is empty. deleteMax :: DMap k f -> DMap k f deleteMax (Bin _ _ _ l Tip) = l deleteMax (Bin _ kx x l r) = balance kx x l (deleteMax r) deleteMax Tip = Tip -- | /O(log n)/. Update the value at the minimal key. updateMinWithKey :: (forall v. k v -> f v -> Maybe (f v)) -> DMap k f -> DMap k f updateMinWithKey f = go where go (Bin sx kx x Tip r) = case f kx x of Nothing -> r Just x' -> Bin sx kx x' Tip r go (Bin _ kx x l r) = balance kx x (go l) r go Tip = Tip -- | /O(log n)/. Update the value at the maximal key. updateMaxWithKey :: (forall v. k v -> f v -> Maybe (f v)) -> DMap k f -> DMap k f updateMaxWithKey f = go where go (Bin sx kx x l Tip) = case f kx x of Nothing -> l Just x' -> Bin sx kx x' l Tip go (Bin _ kx x l r) = balance kx x l (go r) go Tip = Tip {-------------------------------------------------------------------- Union. --------------------------------------------------------------------} -- | The union of a list of maps: -- (@'unions' == 'Prelude.foldl' 'union' 'empty'@). unions :: GCompare k => [DMap k f] -> DMap k f unions ts = foldlStrict union empty ts -- | The union of a list of maps, with a combining operation: -- (@'unionsWithKey' f == 'Prelude.foldl' ('unionWithKey' f) 'empty'@). unionsWithKey :: GCompare k => (forall v. k v -> f v -> f v -> f v) -> [DMap k f] -> DMap k f unionsWithKey f ts = foldlStrict (unionWithKey f) empty ts -- | /O(m*log(n\/m + 1)), m <= n/. -- The expression (@'union' t1 t2@) takes the left-biased union of @t1@ and @t2@. -- It prefers @t1@ when duplicate keys are encountered, -- i.e. (@'union' == 'unionWith' 'const'@). union :: GCompare k => DMap k f -> DMap k f -> DMap k f union t1 Tip = t1 union t1 (Bin _ kx x Tip Tip) = insertR kx x t1 union Tip t2 = t2 union (Bin _ kx x Tip Tip) t2 = insert kx x t2 union t1@(Bin _ k1 x1 l1 r1) t2 = case split k1 t2 of (l2, r2) | l1 `ptrEq` l1l2 && r1 `ptrEq` r1r2 -> t1 | otherwise -> combine k1 x1 l1l2 r1r2 where !l1l2 = l1 `union` l2 !r1r2 = r1 `union` r2 {-------------------------------------------------------------------- Union with a combining function --------------------------------------------------------------------} -- | /O(n+m)/. -- Union with a combining function. unionWithKey :: GCompare k => (forall v. k v -> f v -> f v -> f v) -> DMap k f -> DMap k f -> DMap k f unionWithKey _ t1 Tip = t1 unionWithKey _ Tip t2 = t2 unionWithKey f (Bin _ k1 x1 l1 r1) t2 = case splitLookup k1 t2 of (l2, mx2, r2) -> case mx2 of Nothing -> combine k1 x1 l1l2 r1r2 Just x2 -> combine k1 (f k1 x1 x2) l1l2 r1r2 where !l1l2 = unionWithKey f l1 l2 !r1r2 = unionWithKey f r1 r2 {-------------------------------------------------------------------- Difference --------------------------------------------------------------------} -- | /O(m * log (n\/m + 1)), m <= n/. Difference of two maps. -- Return elements of the first map not existing in the second map. difference :: GCompare k => DMap k f -> DMap k g -> DMap k f difference Tip _ = Tip difference t1 Tip = t1 difference t1 (Bin _ k2 _x2 l2 r2) = case split k2 t1 of (l1, r1) | size t1 == size l1l2 + size r1r2 -> t1 | otherwise -> merge l1l2 r1r2 where !l1l2 = l1 `difference` l2 !r1r2 = r1 `difference` r2 -- | /O(n+m)/. Difference with a combining function. When two equal keys are -- encountered, the combining function is applied to the key and both values. -- If it returns 'Nothing', the element is discarded (proper set difference). If -- it returns (@'Just' y@), the element is updated with a new value @y@. differenceWithKey :: GCompare k => (forall v. k v -> f v -> g v -> Maybe (f v)) -> DMap k f -> DMap k g -> DMap k f differenceWithKey _ Tip _ = Tip differenceWithKey _ t1 Tip = t1 differenceWithKey f (Bin _ k1 x1 l1 r1) t2 = case splitLookup k1 t2 of (l2, mx2, r2) -> case mx2 of Nothing -> combine k1 x1 l1l2 r1r2 Just x2 -> case f k1 x1 x2 of Nothing -> merge l1l2 r1r2 Just x1x2 -> combine k1 x1x2 l1l2 r1r2 where !l1l2 = differenceWithKey f l1 l2 !r1r2 = differenceWithKey f r1 r2 {-------------------------------------------------------------------- Intersection --------------------------------------------------------------------} -- | /O(m * log (n\/m + 1), m <= n/. Intersection of two maps. -- Return data in the first map for the keys existing in both maps. -- (@'intersection' m1 m2 == 'intersectionWith' 'const' m1 m2@). intersection :: GCompare k => DMap k f -> DMap k f -> DMap k f intersection Tip _ = Tip intersection _ Tip = Tip intersection t1@(Bin s1 k1 x1 l1 r1) t2 = let !(l2, found, r2) = splitMember k1 t2 !l1l2 = intersection l1 l2 !r1r2 = intersection r1 r2 in if found then if l1l2 `ptrEq` l1 && r1r2 `ptrEq` r1 then t1 else combine k1 x1 l1l2 r1r2 else merge l1l2 r1r2 -- | /O(m * log (n\/m + 1), m <= n/. Intersection with a combining function. intersectionWithKey :: GCompare k => (forall v. k v -> f v -> g v -> h v) -> DMap k f -> DMap k g -> DMap k h intersectionWithKey _ Tip _ = Tip intersectionWithKey _ _ Tip = Tip intersectionWithKey f (Bin s1 k1 x1 l1 r1) t2 = let !(l2, found, r2) = splitLookup k1 t2 !l1l2 = intersectionWithKey f l1 l2 !r1r2 = intersectionWithKey f r1 r2 in case found of Nothing -> merge l1l2 r1r2 Just x2 -> combine k1 (f k1 x1 x2) l1l2 r1r2 {-------------------------------------------------------------------- Submap --------------------------------------------------------------------} -- | /O(n+m)/. -- This function is defined as (@'isSubmapOf' = 'isSubmapOfBy' 'eqTagged')@). -- isSubmapOf :: forall k f . (GCompare k, Has' Eq k f) => DMap k f -> DMap k f -> Bool isSubmapOf m1 m2 = isSubmapOfBy (\k _ x0 x1 -> has' @Eq @f k (x0 == x1)) m1 m2 {- | /O(n+m)/. The expression (@'isSubmapOfBy' f t1 t2@) returns 'True' if all keys in @t1@ are in tree @t2@, and when @f@ returns 'True' when applied to their respective keys and values. -} isSubmapOfBy :: GCompare k => (forall v. k v -> k v -> f v -> g v -> Bool) -> DMap k f -> DMap k g -> Bool isSubmapOfBy f t1 t2 = (size t1 <= size t2) && (submap' f t1 t2) submap' :: GCompare k => (forall v. k v -> k v -> f v -> g v -> Bool) -> DMap k f -> DMap k g -> Bool submap' _ Tip _ = True submap' _ _ Tip = False submap' f (Bin _ kx x l r) t = case found of Nothing -> False Just (ky, y) -> f kx ky x y && submap' f l lt && submap' f r gt where (lt,found,gt) = splitLookupWithKey kx t -- | /O(n+m)/. Is this a proper submap? (ie. a submap but not equal). -- Defined as (@'isProperSubmapOf' = 'isProperSubmapOfBy' 'eqTagged'@). isProperSubmapOf :: forall k f . (GCompare k, Has' Eq k f) => DMap k f -> DMap k f -> Bool isProperSubmapOf m1 m2 = isProperSubmapOfBy (\k _ x0 x1 -> has' @Eq @f k (x0 == x1)) m1 m2 {- | /O(n+m)/. Is this a proper submap? (ie. a submap but not equal). The expression (@'isProperSubmapOfBy' f m1 m2@) returns 'True' when @m1@ and @m2@ are not equal, all keys in @m1@ are in @m2@, and when @f@ returns 'True' when applied to their respective keys and values. -} isProperSubmapOfBy :: GCompare k => (forall v. k v -> k v -> f v -> g v -> Bool) -> DMap k f -> DMap k g -> Bool isProperSubmapOfBy f t1 t2 = (size t1 < size t2) && (submap' f t1 t2) {-------------------------------------------------------------------- Filter and partition --------------------------------------------------------------------} -- | /O(n)/. Filter all keys\/values that satisfy the predicate. filterWithKey :: GCompare k => (forall v. k v -> f v -> Bool) -> DMap k f -> DMap k f filterWithKey p = go where go Tip = Tip go t@(Bin _ kx x l r) | p kx x = if l' `ptrEq` l && r' `ptrEq` r then t else combine kx x l' r' | otherwise = merge l' r' where !l' = go l !r' = go r -- | /O(n)/. Partition the map according to a predicate. The first -- map contains all elements that satisfy the predicate, the second all -- elements that fail the predicate. See also 'split'. partitionWithKey :: GCompare k => (forall v. k v -> f v -> Bool) -> DMap k f -> (DMap k f, DMap k f) partitionWithKey p0 m0 = toPair (go p0 m0) where go :: GCompare k => (forall v. k v -> f v -> Bool) -> DMap k f -> (DMap k f :*: DMap k f) go _ Tip = (Tip :*: Tip) go p (Bin _ kx x l r) | p kx x = (combine kx x l1 r1 :*: merge l2 r2) | otherwise = (merge l1 r1 :*: combine kx x l2 r2) where (l1 :*: l2) = go p l (r1 :*: r2) = go p r -- | /O(n)/. Map values and collect the 'Just' results. mapMaybe :: GCompare k => (forall v. f v -> Maybe (g v)) -> DMap k f -> DMap k g mapMaybe f = mapMaybeWithKey (const f) -- | /O(n)/. Map keys\/values and collect the 'Just' results. mapMaybeWithKey :: GCompare k => (forall v. k v -> f v -> Maybe (g v)) -> DMap k f -> DMap k g mapMaybeWithKey f = go where go Tip = Tip go (Bin _ kx x l r) = case f kx x of Just y -> combine kx y (go l) (go r) Nothing -> merge (go l) (go r) -- | /O(n)/. Map keys\/values and separate the 'Left' and 'Right' results. mapEitherWithKey :: GCompare k => (forall v. k v -> f v -> Either (g v) (h v)) -> DMap k f -> (DMap k g, DMap k h) mapEitherWithKey f0 = toPair . go f0 where go :: GCompare k => (forall v. k v -> f v -> Either (g v) (h v)) -> DMap k f -> (DMap k g :*: DMap k h) go _ Tip = (Tip :*: Tip) go f (Bin _ kx x l r) = case f kx x of Left y -> (combine kx y l1 r1 :*: merge l2 r2) Right z -> (merge l1 r1 :*: combine kx z l2 r2) where (l1,l2) = mapEitherWithKey f l (r1,r2) = mapEitherWithKey f r {-------------------------------------------------------------------- Mapping --------------------------------------------------------------------} -- | /O(n)/. Map a function over all values in the map. map :: (forall v. f v -> g v) -> DMap k f -> DMap k g map f = go where go Tip = Tip go (Bin sx kx x l r) = Bin sx kx (f x) (go l) (go r) -- | /O(n)/. -- @'ffor' == 'flip' 'map'@ except we cannot actually use -- 'flip' because of the lack of impredicative types. ffor :: DMap k f -> (forall v. f v -> g v) -> DMap k g ffor m f = map f m -- | /O(n)/. Map a function over all values in the map. mapWithKey :: (forall v. k v -> f v -> g v) -> DMap k f -> DMap k g mapWithKey f = go where go Tip = Tip go (Bin sx kx x l r) = Bin sx kx (f kx x) (go l) (go r) -- | /O(n)/. -- @'fforWithKey' == 'flip' 'mapWithKey'@ except we cannot actually use -- 'flip' because of the lack of impredicative types. fforWithKey :: DMap k f -> (forall v. k v -> f v -> g v) -> DMap k g fforWithKey m f = mapWithKey f m -- | /O(n)/. -- @'traverseWithKey' f m == 'fromList' <$> 'traverse' (\(k, v) -> (,) k <$> f k v) ('toList' m)@ -- That is, behaves exactly like a regular 'traverse' except that the traversing -- function also has access to the key associated with a value. traverseWithKey_ :: Applicative t => (forall v. k v -> f v -> t ()) -> DMap k f -> t () traverseWithKey_ f = go where go Tip = pure () go (Bin 1 k v _ _) = f k v go (Bin s k v l r) = go l *> f k v *> go r -- | /O(n)/. -- @'forWithKey' == 'flip' 'traverseWithKey'@ except we cannot actually use -- 'flip' because of the lack of impredicative types. forWithKey_ :: Applicative t => DMap k f -> (forall v. k v -> f v -> t ()) -> t () forWithKey_ m f = traverseWithKey_ f m -- | /O(n)/. -- @'traverseWithKey' f m == 'fromList' <$> 'traverse' (\(k, v) -> (,) k <$> f k v) ('toList' m)@ -- That is, behaves exactly like a regular 'traverse' except that the traversing -- function also has access to the key associated with a value. traverseWithKey :: Applicative t => (forall v. k v -> f v -> t (g v)) -> DMap k f -> t (DMap k g) traverseWithKey f = go where go Tip = pure Tip go (Bin 1 k v _ _) = (\v' -> Bin 1 k v' Tip Tip) <$> f k v go (Bin s k v l r) = flip (Bin s k) <$> go l <*> f k v <*> go r -- | /O(n)/. -- @'forWithKey' == 'flip' 'traverseWithKey'@ except we cannot actually use -- 'flip' because of the lack of impredicative types. forWithKey :: Applicative t => DMap k f -> (forall v. k v -> f v -> t (g v)) -> t (DMap k g) forWithKey m f = traverseWithKey f m -- | /O(n)/. The function 'mapAccumLWithKey' threads an accumulating -- argument through the map in ascending order of keys. mapAccumLWithKey :: (forall v. a -> k v -> f v -> (a, g v)) -> a -> DMap k f -> (a, DMap k g) mapAccumLWithKey f = go where go a Tip = (a,Tip) go a (Bin sx kx x l r) = let (a1,l') = go a l (a2,x') = f a1 kx x (a3,r') = go a2 r in (a3,Bin sx kx x' l' r') -- | /O(n)/. The function 'mapAccumRWithKey' threads an accumulating -- argument through the map in descending order of keys. mapAccumRWithKey :: (forall v. a -> k v -> f v -> (a, g v)) -> a -> DMap k f -> (a, DMap k g) mapAccumRWithKey f = go where go a Tip = (a,Tip) go a (Bin sx kx x l r) = let (a1,r') = go a r (a2,x') = f a1 kx x (a3,l') = go a2 l in (a3,Bin sx kx x' l' r') -- | /O(n*log n)/. -- @'mapKeysWith' c f s@ is the map obtained by applying @f@ to each key of @s@. -- -- The size of the result may be smaller if @f@ maps two or more distinct -- keys to the same new key. In this case the associated values will be -- combined using @c@. mapKeysWith :: GCompare k2 => (forall v. k2 v -> f v -> f v -> f v) -> (forall v. k1 v -> k2 v) -> DMap k1 f -> DMap k2 f mapKeysWith c f = fromListWithKey c . Prelude.map fFirst . toList where fFirst (x :=> y) = (f x :=> y) -- | /O(n)/. -- @'mapKeysMonotonic' f s == 'mapKeys' f s@, but works only when @f@ -- is strictly monotonic. -- That is, for any values @x@ and @y@, if @x@ < @y@ then @f x@ < @f y@. -- /The precondition is not checked./ -- Semi-formally, we have: -- -- > and [x < y ==> f x < f y | x <- ls, y <- ls] -- > ==> mapKeysMonotonic f s == mapKeys f s -- > where ls = keys s -- -- This means that @f@ maps distinct original keys to distinct resulting keys. -- This function has better performance than 'mapKeys'. mapKeysMonotonic :: (forall v. k1 v -> k2 v) -> DMap k1 f -> DMap k2 f mapKeysMonotonic _ Tip = Tip mapKeysMonotonic f (Bin sz k x l r) = Bin sz (f k) x (mapKeysMonotonic f l) (mapKeysMonotonic f r) {-------------------------------------------------------------------- Folds --------------------------------------------------------------------} -- | /O(n)/. Fold the keys and values in the map, such that -- @'foldWithKey' f z == 'Prelude.foldr' ('uncurry' f) z . 'toAscList'@. -- -- This is identical to 'foldrWithKey', and you should use that one instead of -- this one. This name is kept for backward compatibility. foldWithKey :: (forall v. k v -> f v -> b -> b) -> b -> DMap k f -> b foldWithKey = foldrWithKey {-# DEPRECATED foldWithKey "Use foldrWithKey instead" #-} -- | /O(n)/. Post-order fold. The function will be applied from the lowest -- value to the highest. foldrWithKey :: (forall v. k v -> f v -> b -> b) -> b -> DMap k f -> b foldrWithKey f = go where go z Tip = z go z (Bin _ kx x l r) = go (f kx x (go z r)) l -- | /O(n)/. Pre-order fold. The function will be applied from the highest -- value to the lowest. foldlWithKey :: (forall v. b -> k v -> f v -> b) -> b -> DMap k f -> b foldlWithKey f = go where go z Tip = z go z (Bin _ kx x l r) = go (f (go z l) kx x) r {- -- | /O(n)/. A strict version of 'foldlWithKey'. foldlWithKey' :: (b -> k -> a -> b) -> b -> DMap k -> b foldlWithKey' f = go where go z Tip = z go z (Bin _ kx x l r) = z `seq` go (f (go z l) kx x) r -} {-------------------------------------------------------------------- List variations --------------------------------------------------------------------} -- | /O(n)/. Return all keys of the map in ascending order. -- -- > keys (fromList [(5,"a"), (3,"b")]) == [3,5] -- > keys empty == [] keys :: DMap k f -> [Some k] keys m = [mkSome k | (k :=> _) <- assocs m] -- | /O(n)/. Return all key\/value pairs in the map in ascending key order. assocs :: DMap k f -> [DSum k f] assocs m = toList m {-------------------------------------------------------------------- Lists use [foldlStrict] to reduce demand on the control-stack --------------------------------------------------------------------} -- | /O(n*log n)/. Build a map from a list of key\/value pairs. See also 'fromAscList'. -- If the list contains more than one value for the same key, the last value -- for the key is retained. fromList :: GCompare k => [DSum k f] -> DMap k f fromList xs = foldlStrict ins empty xs where ins :: GCompare k => DMap k f -> DSum k f -> DMap k f ins t (k :=> x) = insert k x t -- | /O(n*log n)/. Build a map from a list of key\/value pairs with a combining function. See also 'fromAscListWithKey'. fromListWithKey :: GCompare k => (forall v. k v -> f v -> f v -> f v) -> [DSum k f] -> DMap k f fromListWithKey f xs = foldlStrict (ins f) empty xs where ins :: GCompare k => (forall v. k v -> f v -> f v -> f v) -> DMap k f -> DSum k f -> DMap k f ins f t (k :=> x) = insertWithKey f k x t -- | /O(n)/. Convert to a list of key\/value pairs. toList :: DMap k f -> [DSum k f] toList t = toAscList t -- | /O(n)/. Convert to an ascending list. toAscList :: DMap k f -> [DSum k f] toAscList t = foldrWithKey (\k x xs -> (k :=> x):xs) [] t -- | /O(n)/. Convert to a descending list. toDescList :: DMap k f -> [DSum k f] toDescList t = foldlWithKey (\xs k x -> (k :=> x):xs) [] t {-------------------------------------------------------------------- Building trees from ascending/descending lists can be done in linear time. Note that if [xs] is ascending that: fromAscList xs == fromList xs fromAscListWith f xs == fromListWith f xs --------------------------------------------------------------------} -- | /O(n)/. Build a map from an ascending list in linear time. -- /The precondition (input list is ascending) is not checked./ fromAscList :: GEq k => [DSum k f] -> DMap k f fromAscList xs = fromAscListWithKey (\_ x _ -> x) xs -- | /O(n)/. Build a map from an ascending list in linear time with a -- combining function for equal keys. -- /The precondition (input list is ascending) is not checked./ fromAscListWithKey :: GEq k => (forall v. k v -> f v -> f v -> f v) -> [DSum k f] -> DMap k f fromAscListWithKey f xs = fromDistinctAscList (combineEq f xs) where -- [combineEq f xs] combines equal elements with function [f] in an ordered list [xs] combineEq _ xs' = case xs' of [] -> [] [x] -> [x] (x:xx) -> combineEq' f x xx combineEq' :: GEq k => (forall v. k v -> f v -> f v -> f v) -> DSum k f -> [DSum k f] -> [DSum k f] combineEq' f z [] = [z] combineEq' f z@(kz :=> zz) (x@(kx :=> xx):xs') = case geq kx kz of Just Refl -> let yy = f kx xx zz in combineEq' f (kx :=> yy) xs' Nothing -> z : combineEq' f x xs' -- | /O(n)/. Build a map from an ascending list of distinct elements in linear time. -- /The precondition is not checked./ fromDistinctAscList :: [DSum k f] -> DMap k f fromDistinctAscList xs = build const (length xs) xs where -- 1) use continutations so that we use heap space instead of stack space. -- 2) special case for n==5 to build bushier trees. build :: (DMap k f -> [DSum k f] -> b) -> Int -> [DSum k f] -> b build c 0 xs' = c Tip xs' build c 5 xs' = case xs' of ((k1:=>x1):(k2:=>x2):(k3:=>x3):(k4:=>x4):(k5:=>x5):xx) -> c (bin k4 x4 (bin k2 x2 (singleton k1 x1) (singleton k3 x3)) (singleton k5 x5)) xx _ -> error "fromDistinctAscList build" build c n xs' = seq nr $ build (buildR nr c) nl xs' where nl = n `div` 2 nr = n - nl - 1 buildR :: Int -> (DMap k f -> [DSum k f] -> b) -> DMap k f -> [DSum k f] -> b buildR n c l ((k:=>x):ys) = build (buildB l k x c) n ys buildR _ _ _ [] = error "fromDistinctAscList buildR []" buildB :: DMap k f -> k v -> f v -> (DMap k f -> a -> b) -> DMap k f -> a -> b buildB l k x c r zs = c (bin k x l r) zs {-------------------------------------------------------------------- Split --------------------------------------------------------------------} -- | /O(log n)/. The expression (@'split' k map@) is a pair @(map1,map2)@ where -- the keys in @map1@ are smaller than @k@ and the keys in @map2@ larger than @k@. -- Any key equal to @k@ is found in neither @map1@ nor @map2@. split :: forall k f v. GCompare k => k v -> DMap k f -> (DMap k f, DMap k f) split k = toPair . go where go :: DMap k f -> (DMap k f :*: DMap k f) go Tip = (Tip :*: Tip) go (Bin _ kx x l r) = case gcompare k kx of GLT -> let !(lt :*: gt) = go l in (lt :*: combine kx x gt r) GGT -> let !(lt :*: gt) = go r in (combine kx x l lt :*: gt) GEQ -> (l :*: r) {-# INLINABLE split #-} -- | /O(log n)/. The expression (@'splitLookup' k map@) splits a map just -- like 'split' but also returns @'lookup' k map@. splitLookup :: forall k f v. GCompare k => k v -> DMap k f -> (DMap k f, Maybe (f v), DMap k f) splitLookup k = toTriple . go where go :: DMap k f -> Triple' (DMap k f) (Maybe (f v)) (DMap k f) go Tip = Triple' Tip Nothing Tip go (Bin _ kx x l r) = case gcompare k kx of GLT -> let !(Triple' lt z gt) = go l in Triple' lt z (combine kx x gt r) GGT -> let !(Triple' lt z gt) = go r in Triple' (combine kx x l lt) z gt GEQ -> Triple' l (Just x) r -- | /O(log n)/. The expression (@'splitMember' k map@) splits a map just -- like 'split' but also returns @'member' k map@. splitMember :: forall k f v. GCompare k => k v -> DMap k f -> (DMap k f, Bool, DMap k f) splitMember k = toTriple . go where go :: DMap k f -> Triple' (DMap k f) Bool (DMap k f) go Tip = Triple' Tip False Tip go (Bin _ kx x l r) = case gcompare k kx of GLT -> let !(Triple' lt z gt) = go l in Triple' lt z (combine kx x gt r) GGT -> let !(Triple' lt z gt) = go r in Triple' (combine kx x l lt) z gt GEQ -> Triple' l True r -- | /O(log n)/. splitLookupWithKey :: forall k f v. GCompare k => k v -> DMap k f -> (DMap k f, Maybe (k v, f v), DMap k f) splitLookupWithKey k = toTriple . go where go :: DMap k f -> Triple' (DMap k f) (Maybe (k v, f v)) (DMap k f) go Tip = Triple' Tip Nothing Tip go (Bin _ kx x l r) = case gcompare k kx of GLT -> let !(Triple' lt z gt) = go l in Triple' lt z (combine kx x gt r) GGT -> let !(Triple' lt z gt) = go r in Triple' (combine kx x l lt) z gt GEQ -> Triple' l (Just (kx, x)) r {-------------------------------------------------------------------- Eq converts the tree to a list. In a lazy setting, this actually seems one of the faster methods to compare two trees and it is certainly the simplest :-) --------------------------------------------------------------------} instance (GEq k, Has' Eq k f) => Eq (DMap k f) where t1 == t2 = (size t1 == size t2) && (toAscList t1 == toAscList t2) {-------------------------------------------------------------------- Ord --------------------------------------------------------------------} instance (GCompare k, Has' Eq k f, Has' Ord k f) => Ord (DMap k f) where compare m1 m2 = compare (toAscList m1) (toAscList m2) {-------------------------------------------------------------------- Read --------------------------------------------------------------------} instance (GCompare k, GRead k, Has' Read k f) => Read (DMap k f) where readPrec = parens $ prec 10 $ do Ident "fromList" <- lexP xs <- readPrec return (fromList xs) readListPrec = readListPrecDefault {-------------------------------------------------------------------- Show --------------------------------------------------------------------} instance (GShow k, Has' Show k f) => Show (DMap k f) where showsPrec p m = showParen (p>10) ( showString "fromList " . showsPrec 11 (toList m) ) -- | /O(n)/. Show the tree that implements the map. The tree is shown -- in a compressed, hanging format. See 'showTreeWith'. showTree :: (GShow k, Has' Show k f) => DMap k f -> String showTree m = showTreeWith showElem True False m where showElem :: (GShow k, Has' Show k f) => k v -> f v -> String showElem k x = show (k :=> x) {- | /O(n)/. The expression (@'showTreeWith' showelem hang wide map@) shows the tree that implements the map. Elements are shown using the @showElem@ function. If @hang@ is 'True', a /hanging/ tree is shown otherwise a rotated tree is shown. If @wide@ is 'True', an extra wide version is shown. -} showTreeWith :: (forall v. k v -> f v -> String) -> Bool -> Bool -> DMap k f -> String showTreeWith showelem hang wide t | hang = (showsTreeHang showelem wide [] t) "" | otherwise = (showsTree showelem wide [] [] t) "" showsTree :: (forall v. k v -> f v -> String) -> Bool -> [String] -> [String] -> DMap k f -> ShowS showsTree showelem wide lbars rbars t = case t of Tip -> showsBars lbars . showString "|\n" Bin _ kx x Tip Tip -> showsBars lbars . showString (showelem kx x) . showString "\n" Bin _ kx x l r -> showsTree showelem wide (withBar rbars) (withEmpty rbars) r . showWide wide rbars . showsBars lbars . showString (showelem kx x) . showString "\n" . showWide wide lbars . showsTree showelem wide (withEmpty lbars) (withBar lbars) l showsTreeHang :: (forall v. k v -> f v -> String) -> Bool -> [String] -> DMap k f -> ShowS showsTreeHang showelem wide bars t = case t of Tip -> showsBars bars . showString "|\n" Bin _ kx x Tip Tip -> showsBars bars . showString (showelem kx x) . showString "\n" Bin _ kx x l r -> showsBars bars . showString (showelem kx x) . showString "\n" . showWide wide bars . showsTreeHang showelem wide (withBar bars) l . showWide wide bars . showsTreeHang showelem wide (withEmpty bars) r showWide :: Bool -> [String] -> String -> String showWide wide bars | wide = showString (concat (reverse bars)) . showString "|\n" | otherwise = id showsBars :: [String] -> ShowS showsBars bars = case bars of [] -> id _ -> showString (concat (reverse (tail bars))) . showString node node :: String node = "+--" withBar, withEmpty :: [String] -> [String] withBar bars = "| ":bars withEmpty bars = " ":bars {-------------------------------------------------------------------- Assertions --------------------------------------------------------------------} -- | /O(n)/. Test if the internal map structure is valid. valid :: GCompare k => DMap k f -> Bool valid t = balanced t && ordered t && validsize t ordered :: GCompare k => DMap k f -> Bool ordered t = bounded (const True) (const True) t where bounded :: GCompare k => (Some k -> Bool) -> (Some k -> Bool) -> DMap k f -> Bool bounded lo hi t' = case t' of Tip -> True Bin _ kx _ l r -> lo (mkSome kx) && hi (mkSome kx) && bounded lo (< mkSome kx) l && bounded (> mkSome kx) hi r -- | Exported only for "Debug.QuickCheck" balanced :: DMap k f -> Bool balanced t = case t of Tip -> True Bin _ _ _ l r -> (size l + size r <= 1 || (size l <= delta*size r && size r <= delta*size l)) && balanced l && balanced r validsize :: DMap k f -> Bool validsize t = (realsize t == Just (size t)) where realsize t' = case t' of Tip -> Just 0 Bin sz _ _ l r -> case (realsize l,realsize r) of (Just n,Just m) | n+m+1 == sz -> Just sz _ -> Nothing {-------------------------------------------------------------------- Utilities --------------------------------------------------------------------} foldlStrict :: (a -> b -> a) -> a -> [b] -> a foldlStrict f = go where go z [] = z go z (x:xs) = z `seq` go (f z x) xs dependent-map-0.4.0.0/src/Data/Dependent/Map/0000755000000000000000000000000007346545000016646 5ustar0000000000000000dependent-map-0.4.0.0/src/Data/Dependent/Map/Internal.hs0000644000000000000000000003511507346545000020763 0ustar0000000000000000{-# LANGUAGE BangPatterns #-} {-# LANGUAGE DeriveDataTypeable #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE PolyKinds #-} {-# LANGUAGE Safe #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeOperators #-} module Data.Dependent.Map.Internal where import Data.Dependent.Sum (DSum((:=>))) import Data.GADT.Compare (GCompare, GOrdering(..), gcompare) import Data.Some (Some, mkSome, withSome) import Data.Typeable (Typeable) -- |Dependent maps: 'k' is a GADT-like thing with a facility for -- rediscovering its type parameter, elements of which function as identifiers -- tagged with the type of the thing they identify. Real GADTs are one -- useful instantiation of @k@, as are 'Tag's from "Data.Unique.Tag" in the -- 'prim-uniq' package. -- -- Semantically, @'DMap' k f@ is equivalent to a set of @'DSum' k f@ where no two -- elements have the same tag. -- -- More informally, 'DMap' is to dependent products as 'M.Map' is to @(->)@. -- Thus it could also be thought of as a partial (in the sense of \"partial -- function\") dependent product. data DMap k f where Tip :: DMap k f Bin :: {- sz -} !Int -> {- key -} !(k v) -> {- value -} f v -> {- left -} !(DMap k f) -> {- right -} !(DMap k f) -> DMap k f deriving Typeable {-------------------------------------------------------------------- Construction --------------------------------------------------------------------} -- | /O(1)/. The empty map. -- -- > empty == fromList [] -- > size empty == 0 empty :: DMap k f empty = Tip -- | /O(1)/. A map with a single element. -- -- > singleton 1 'a' == fromList [(1, 'a')] -- > size (singleton 1 'a') == 1 singleton :: k v -> f v -> DMap k f singleton k x = Bin 1 k x Tip Tip {-------------------------------------------------------------------- Query --------------------------------------------------------------------} -- | /O(1)/. Is the map empty? null :: DMap k f -> Bool null Tip = True null Bin{} = False -- | /O(1)/. The number of elements in the map. size :: DMap k f -> Int size Tip = 0 size (Bin n _ _ _ _) = n -- | /O(log n)/. Lookup the value at a key in the map. -- -- The function will return the corresponding value as @('Just' value)@, -- or 'Nothing' if the key isn't in the map. lookup :: forall k f v. GCompare k => k v -> DMap k f -> Maybe (f v) lookup k = k `seq` go where go :: DMap k f -> Maybe (f v) go Tip = Nothing go (Bin _ kx x l r) = case gcompare k kx of GLT -> go l GGT -> go r GEQ -> Just x lookupAssoc :: forall k f v. GCompare k => Some k -> DMap k f -> Maybe (DSum k f) lookupAssoc sk = withSome sk $ \k -> let go :: DMap k f -> Maybe (DSum k f) go Tip = Nothing go (Bin _ kx x l r) = case gcompare k kx of GLT -> go l GGT -> go r GEQ -> Just (kx :=> x) in k `seq` go {-------------------------------------------------------------------- Utility functions that maintain the balance properties of the tree. All constructors assume that all values in [l] < [k] and all values in [r] > [k], and that [l] and [r] are valid trees. In order of sophistication: [Bin sz k x l r] The type constructor. [bin k x l r] Maintains the correct size, assumes that both [l] and [r] are balanced with respect to each other. [balance k x l r] Restores the balance and size. Assumes that the original tree was balanced and that [l] or [r] has changed by at most one element. [combine k x l r] Restores balance and size. Furthermore, we can construct a new tree from two trees. Both operations assume that all values in [l] < all values in [r] and that [l] and [r] are valid: [glue l r] Glues [l] and [r] together. Assumes that [l] and [r] are already balanced with respect to each other. [merge l r] Merges two trees and restores balance. Note: in contrast to Adam's paper, we use (<=) comparisons instead of (<) comparisons in [combine], [merge] and [balance]. Quickcheck (on [difference]) showed that this was necessary in order to maintain the invariants. It is quite unsatisfactory that I haven't been able to find out why this is actually the case! Fortunately, it doesn't hurt to be a bit more conservative. --------------------------------------------------------------------} {-------------------------------------------------------------------- Combine --------------------------------------------------------------------} combine :: GCompare k => k v -> f v -> DMap k f -> DMap k f -> DMap k f combine kx x Tip r = insertMin kx x r combine kx x l Tip = insertMax kx x l combine kx x l@(Bin sizeL ky y ly ry) r@(Bin sizeR kz z lz rz) | delta*sizeL <= sizeR = balance kz z (combine kx x l lz) rz | delta*sizeR <= sizeL = balance ky y ly (combine kx x ry r) | otherwise = bin kx x l r -- insertMin and insertMax don't perform potentially expensive comparisons. insertMax,insertMin :: k v -> f v -> DMap k f -> DMap k f insertMax kx x t = case t of Tip -> singleton kx x Bin _ ky y l r -> balance ky y l (insertMax kx x r) insertMin kx x t = case t of Tip -> singleton kx x Bin _ ky y l r -> balance ky y (insertMin kx x l) r {-------------------------------------------------------------------- [merge l r]: merges two trees. --------------------------------------------------------------------} merge :: DMap k f -> DMap k f -> DMap k f merge Tip r = r merge l Tip = l merge l@(Bin sizeL kx x lx rx) r@(Bin sizeR ky y ly ry) | delta*sizeL <= sizeR = balance ky y (merge l ly) ry | delta*sizeR <= sizeL = balance kx x lx (merge rx r) | otherwise = glue l r {-------------------------------------------------------------------- [glue l r]: glues two trees together. Assumes that [l] and [r] are already balanced with respect to each other. --------------------------------------------------------------------} glue :: DMap k f -> DMap k f -> DMap k f glue Tip r = r glue l Tip = l glue l r | size l > size r = case deleteFindMax l of (km :=> m,l') -> balance km m l' r | otherwise = case deleteFindMin r of (km :=> m,r') -> balance km m l r' -- | /O(log n)/. Delete and find the minimal element. -- -- > deleteFindMin (fromList [(5,"a"), (3,"b"), (10,"c")]) == ((3,"b"), fromList[(5,"a"), (10,"c")]) -- > deleteFindMin Error: can not return the minimal element of an empty map deleteFindMin :: DMap k f -> (DSum k f, DMap k f) deleteFindMin t = case minViewWithKey t of Nothing -> (error "Map.deleteFindMin: can not return the minimal element of an empty map", Tip) Just p -> p -- | A strict pair. data (:*:) a b = !a :*: !b infixr 1 :*: -- | Convert a strict pair to a pair. toPair :: a :*: b -> (a, b) toPair (a :*: b) = (a, b) {-# INLINE toPair #-} data Triple' a b c = Triple' !a !b !c -- | Convert a strict triple to a triple. toTriple :: Triple' a b c -> (a, b, c) toTriple (Triple' a b c) = (a, b, c) {-# INLINE toTriple #-} -- | /O(log n)/. Retrieves the minimal (key :=> value) entry of the map, and -- the map stripped of that element, or 'Nothing' if passed an empty map. minViewWithKey :: forall k f . DMap k f -> Maybe (DSum k f, DMap k f) minViewWithKey Tip = Nothing minViewWithKey (Bin _ k0 x0 l0 r0) = Just $! toPair $ go k0 x0 l0 r0 where go :: k v -> f v -> DMap k f -> DMap k f -> DSum k f :*: DMap k f go k x Tip r = (k :=> x) :*: r go k x (Bin _ kl xl ll lr) r = let !(km :*: l') = go kl xl ll lr in (km :*: balance k x l' r) -- | /O(log n)/. Retrieves the maximal (key :=> value) entry of the map, and -- the map stripped of that element, or 'Nothing' if passed an empty map. maxViewWithKey :: forall k f . DMap k f -> Maybe (DSum k f, DMap k f) maxViewWithKey Tip = Nothing maxViewWithKey (Bin _ k0 x0 l0 r0) = Just $! toPair $ go k0 x0 l0 r0 where go :: k v -> f v -> DMap k f -> DMap k f -> DSum k f :*: DMap k f go k x l Tip = (k :=> x) :*: l go k x l (Bin _ kr xr rl rr) = let !(km :*: r') = go kr xr rl rr in (km :*: balance k x l r') -- | /O(log n)/. Delete and find the maximal element. -- -- > deleteFindMax (fromList [(5,"a"), (3,"b"), (10,"c")]) == ((10,"c"), fromList [(3,"b"), (5,"a")]) -- > deleteFindMax empty Error: can not return the maximal element of an empty map deleteFindMax :: DMap k f -> (DSum k f, DMap k f) deleteFindMax t = case t of Bin _ k x l Tip -> (k :=> x,l) Bin _ k x l r -> let (km,r') = deleteFindMax r in (km,balance k x l r') Tip -> (error "Map.deleteFindMax: can not return the maximal element of an empty map", Tip) {-------------------------------------------------------------------- [balance l x r] balances two trees with value x. The sizes of the trees should balance after decreasing the size of one of them. (a rotation). [delta] is the maximal relative difference between the sizes of two trees, it corresponds with the [w] in Adams' paper. [ratio] is the ratio between an outer and inner sibling of the heavier subtree in an unbalanced setting. It determines whether a double or single rotation should be performed to restore balance. It corresponds with the inverse of $\alpha$ in Adam's article. Note that: - [delta] should be larger than 4.646 with a [ratio] of 2. - [delta] should be larger than 3.745 with a [ratio] of 1.534. - A lower [delta] leads to a more 'perfectly' balanced tree. - A higher [delta] performs less rebalancing. - Balancing is automatic for random data and a balancing scheme is only necessary to avoid pathological worst cases. Almost any choice will do, and in practice, a rather large [delta] may perform better than smaller one. Note: in contrast to Adam's paper, we use a ratio of (at least) [2] to decide whether a single or double rotation is needed. Although he actually proves that this ratio is needed to maintain the invariants, his implementation uses an invalid ratio of [1]. --------------------------------------------------------------------} delta,ratio :: Int delta = 4 ratio = 2 balance :: k v -> f v -> DMap k f -> DMap k f -> DMap k f balance k x l r | sizeL + sizeR <= 1 = Bin sizeX k x l r | sizeR >= delta*sizeL = rotateL k x l r | sizeL >= delta*sizeR = rotateR k x l r | otherwise = Bin sizeX k x l r where sizeL = size l sizeR = size r sizeX = sizeL + sizeR + 1 -- rotate rotateL :: k v -> f v -> DMap k f -> DMap k f -> DMap k f rotateL k x l r@(Bin _ _ _ ly ry) | size ly < ratio*size ry = singleL k x l r | otherwise = doubleL k x l r rotateL _ _ _ Tip = error "rotateL Tip" rotateR :: k v -> f v -> DMap k f -> DMap k f -> DMap k f rotateR k x l@(Bin _ _ _ ly ry) r | size ry < ratio*size ly = singleR k x l r | otherwise = doubleR k x l r rotateR _ _ Tip _ = error "rotateR Tip" -- basic rotations singleL, singleR :: k v -> f v -> DMap k f -> DMap k f -> DMap k f singleL k1 x1 t1 (Bin _ k2 x2 t2 t3) = bin k2 x2 (bin k1 x1 t1 t2) t3 singleL _ _ _ Tip = error "singleL Tip" singleR k1 x1 (Bin _ k2 x2 t1 t2) t3 = bin k2 x2 t1 (bin k1 x1 t2 t3) singleR _ _ Tip _ = error "singleR Tip" doubleL, doubleR :: k v -> f v -> DMap k f -> DMap k f -> DMap k f doubleL k1 x1 t1 (Bin _ k2 x2 (Bin _ k3 x3 t2 t3) t4) = bin k3 x3 (bin k1 x1 t1 t2) (bin k2 x2 t3 t4) doubleL _ _ _ _ = error "doubleL" doubleR k1 x1 (Bin _ k2 x2 t1 (Bin _ k3 x3 t2 t3)) t4 = bin k3 x3 (bin k2 x2 t1 t2) (bin k1 x1 t3 t4) doubleR _ _ _ _ = error "doubleR" {-------------------------------------------------------------------- The bin constructor maintains the size of the tree --------------------------------------------------------------------} bin :: k v -> f v -> DMap k f -> DMap k f -> DMap k f bin k x l r = Bin (size l + size r + 1) k x l r {-------------------------------------------------------------------- Utility functions that return sub-ranges of the original tree. Some functions take a comparison function as argument to allow comparisons against infinite values. A function [cmplo k] should be read as [compare lo k]. [trim cmplo cmphi t] A tree that is either empty or where [cmplo k == LT] and [cmphi k == GT] for the key [k] of the root. [filterGt cmp t] A tree where for all keys [k]. [cmp k == LT] [filterLt cmp t] A tree where for all keys [k]. [cmp k == GT] [split k t] Returns two trees [l] and [r] where all keys in [l] are <[k] and all keys in [r] are >[k]. [splitLookup k t] Just like [split] but also returns whether [k] was found in the tree. --------------------------------------------------------------------} {-------------------------------------------------------------------- [trim lo hi t] trims away all subtrees that surely contain no values between the range [lo] to [hi]. The returned tree is either empty or the key of the root is between @lo@ and @hi@. --------------------------------------------------------------------} trim :: (Some k -> Ordering) -> (Some k -> Ordering) -> DMap k f -> DMap k f trim _ _ Tip = Tip trim cmplo cmphi t@(Bin _ kx _ l r) = case cmplo (mkSome kx) of LT -> case cmphi (mkSome kx) of GT -> t _ -> trim cmplo cmphi l _ -> trim cmplo cmphi r trimLookupLo :: GCompare k => Some k -> (Some k -> Ordering) -> DMap k f -> (Maybe (DSum k f), DMap k f) trimLookupLo _ _ Tip = (Nothing,Tip) trimLookupLo lo cmphi t@(Bin _ kx x l r) = case compare lo (mkSome kx) of LT -> case cmphi (mkSome kx) of GT -> (lookupAssoc lo t, t) _ -> trimLookupLo lo cmphi l GT -> trimLookupLo lo cmphi r EQ -> (Just (kx :=> x),trim (compare lo) cmphi r) {-------------------------------------------------------------------- [filterGt k t] filter all keys >[k] from tree [t] [filterLt k t] filter all keys <[k] from tree [t] --------------------------------------------------------------------} filterGt :: GCompare k => (Some k -> Ordering) -> DMap k f -> DMap k f filterGt cmp = go where go Tip = Tip go (Bin _ kx x l r) = case cmp (mkSome kx) of LT -> combine kx x (go l) r GT -> go r EQ -> r filterLt :: GCompare k => (Some k -> Ordering) -> DMap k f -> DMap k f filterLt cmp = go where go Tip = Tip go (Bin _ kx x l r) = case cmp (mkSome kx) of LT -> go l GT -> combine kx x l (go r) EQ -> l dependent-map-0.4.0.0/src/Data/Dependent/Map/Lens.hs0000644000000000000000000000636707346545000020117 0ustar0000000000000000{-# LANGUAGE PolyKinds #-} -- | -- Some functions for using lenses with 'DMap'. module Data.Dependent.Map.Lens ( -- * At dmat -- * Ix , dmix ) where import Prelude hiding (lookup) import Data.Dependent.Map (DMap, alterF, insert, lookup) import Data.GADT.Compare (GCompare) -- | -- These functions have been specialised for use with 'DMap' but without any of the -- specific 'lens' types used so that we have compatibility without needing the -- dependency just for these functions. -- -- | -- This is equivalent to the from : -- -- @ -- type Lens s t a b = forall f. Functor f => (a -> f b) -> s -> f t -- -- at :: Index m -> Lens' m (Maybe (IxValue m)) -- @ -- -- So the type of 'dmat' is equivalent to: -- -- @ -- dmat :: GCompare k => Lens' (DMap k f) (Maybe (f v)) -- @ -- -- >>> DMap.fromList [AInt :=> Identity 33, AFloat :=> Identity 3.5] & dmat AString ?~ "Hat" -- DMap.fromList [AString :=> Identity "Hat", AInt :=> Identity 33, AFloat :=> Identity 3.5] -- -- >>> DMap.fromList [AString :=> Identity "Shoe", AInt :=> Identity 33, AFloat :=> Identity 3.5] ^? dmat AFloat -- Just (AFloat :=> 3.5) -- dmat :: (GCompare k, Functor f) => k v -> (Maybe (g v) -> f (Maybe (g v))) -> DMap k g -> f (DMap k g) dmat k f = alterF k f {-# INLINE dmat #-} -- | -- This is equivalent to the from : -- -- @ -- type Traversal s t a b = forall f. Applicative f => (a -> f b) -> s -> f t -- -- ix :: Index m -> Traversal' m (IxValue m) -- @ -- -- So the type of 'dmix' is equivalent to: -- -- @ -- dmix :: GCompare k => k v -> Traversal' (DMap k f) (f v) -- @ -- -- /NB:/ Setting the value of this -- -- will only set the value in 'dmix' if it is already present. -- -- If you want to be able to insert /missing/ values, you want 'dmat'. -- -- >>> DMap.fromList [AString :=> Identity "Shoe", AInt :=> Identity 33, AFloat :=> Identity 3.5] & dmix AInt %~ f -- DMap.fromList [AString :=> Identity "Shoe", AInt :=> Identity (f 33), AFloat :=> Identity 3.5] -- -- >>> DMap.fromList [AString :=> Identity "Shoe", AInt :=> Identity 33, AFloat :=> Identity 3.5] & dmix AString .~ "Hat" -- DMap.fromList [AString :=> Identity "Hat", AInt :=> Identity 33, AFloat :=> Identity 3.5] -- -- >>> DMap.fromList [AString :=> Identity "Shoe", AInt :=> Identity 33, AFloat :=> Identity 3.5] ^? dmix AFloat -- Just (AFloat :=> 3.5) -- -- >>> DMap.fromList [AString :=> Identity "Shoe", AFloat :=> Identity 3.5] ^? dmix AInt -- Nothing dmix :: (GCompare k, Applicative f) => k v -> (g v -> f (g v)) -> DMap k g -> f (DMap k g) dmix k f dmap = maybe (pure dmap) (fmap (flip (insert k) dmap) . f) $ lookup k dmap {-# INLINE dmix #-} dependent-map-0.4.0.0/src/Data/Dependent/Map/PtrEquality.hs0000644000000000000000000000227307346545000021471 0ustar0000000000000000{-# LANGUAGE MagicHash #-} {-# OPTIONS_HADDOCK hide #-} -- | Really unsafe pointer equality -- -- = WARNING -- -- This module is considered __internal__. -- -- The Package Versioning Policy __does not apply__. -- -- The contents of this module may change __in any way whatsoever__ -- and __without any warning__ between minor versions of this package. -- -- Authors importing this module are expected to track development -- closely. module Data.Dependent.Map.PtrEquality (ptrEq, hetPtrEq) where import Unsafe.Coerce (unsafeCoerce) import GHC.Exts (isTrue#, reallyUnsafePtrEquality#) -- | Checks if two pointers are equal. Yes means yes; -- no means maybe. The values should be forced to at least -- WHNF before comparison to get moderately reliable results. ptrEq :: a -> a -> Bool -- | Checks if two pointers are equal, without requiring -- them to have the same type. The values should be forced -- to at least WHNF before comparison to get moderately -- reliable results. hetPtrEq :: a -> b -> Bool ptrEq x y = isTrue# (reallyUnsafePtrEquality# x y) hetPtrEq x y = isTrue# (unsafeCoerce reallyUnsafePtrEquality# x y) {-# INLINE ptrEq #-} {-# INLINE hetPtrEq #-} infix 4 `ptrEq` infix 4 `hetPtrEq`