{-# LANGUAGE Haskell2010 , GeneralizedNewtypeDeriving , DeriveDataTypeable #-} {-# OPTIONS -Wall -fno-warn-missing-signatures #-} module Utils where import Data.Strings import Data.List (foldl') import Data.Set (Set) import qualified Data.Set as Set import qualified Data.Bimap as Bimap (>>>) = flip (.) intersections :: Ord a => [Set a] -> Set a intersections sets = case sets of [] -> Set.empty [x] -> x (x:xs) -> foldl' Set.intersection x xs uneither :: Either a a -> a uneither = either id id -- Following 20 lines: Functions for managing a Bimap -- such that it works with case insensitive string. -- -- TODO: Factor this out `plus` use the case-insensitive package. -- Those functions x... should be made into their own -- datatype (Something like CISBimap or -- BimapWithGenericComparisonFunction or ...) newtype CaseInsensitiveString = CIS String deriving Show instance Eq CaseInsensitiveString where (CIS a) == (CIS b) = strToLower a == strToLower b instance Ord CaseInsensitiveString where (CIS a) <= (CIS b) = strToLower a <= strToLower b xToString (CIS s) = s xEmpty = Bimap.empty xInsert k v = Bimap.insert (CIS k) (CIS v) xMemberR k = Bimap.memberR (CIS k) xLookup :: Bimap.Bimap CaseInsensitiveString CaseInsensitiveString -> String -> Maybe String xLookup m = maybe Nothing (Just . xToString) . (flip Bimap.lookup m) . CIS xLookupR :: Bimap.Bimap CaseInsensitiveString CaseInsensitiveString -> String -> Maybe String xLookupR m = maybe Nothing (Just . xToString) . (flip Bimap.lookupR m) . CIS xFromList = Bimap.fromList . map (\(a, b) -> (CIS a, CIS b)) xToList = map (\(a, b) -> (xToString a, xToString b)) . Bimap.toList xKeysR = map xToString . Bimap.keysR xKeys = map xToString . Bimap.keys xSize = Bimap.size -- end todo