{-# LANGUAGE TypeFamilies, MultiParamTypeClasses #-} module Data.TrieMap.UnitMap where import Data.TrieMap.TrieKey import Control.Applicative import Data.Foldable import Data.Traversable import Data.Maybe import Prelude hiding (foldr, foldl) type instance TrieMap () = Maybe instance TrieKey () Maybe where emptyM = Nothing nullM = isNothing sizeM = maybe 0 lookupM = flip const lookupIxM _ _ m = (empty, Asc 0 () <$> m, empty) assocAtM s i m = case m of Nothing -> (empty, empty, empty) Just m | i < 0 -> (empty, empty, return (Asc 0 () m)) | i < s m -> (empty, return (Asc 0 () m), empty) | otherwise -> (return (Asc 0 () m), empty, empty) traverseWithKeyM _ f = traverse (f ()) foldWithKeyM f m z = foldr (f ()) z m foldlWithKeyM f m z = foldl (f ()) z m mapEitherM _ _ f = maybe (Nothing, Nothing) (f ()) splitLookupM _ f _ = maybe (Nothing, Nothing, Nothing) f alterM _ f _ = f alterLookupM _ f _ = f unionM _ f = unionMaybe (f ()) isectM _ f = isectMaybe (f ()) diffM _ f = diffMaybe (f ()) extractM _ f = maybe empty (f ()) isSubmapM (<=) = subMaybe (<=) fromListM _ f [] = Nothing fromListM _ f ((_, v):xs) = Just (foldl (\ v' -> f () v' . snd) v xs) fromAscListM = fromListM