module Yi.Utils where
import Control.Applicative
import Control.Lens hiding (cons)
import Control.Monad.Base
import Data.Binary
import Data.Char (toLower)
import Data.Foldable hiding (all,any)
import qualified Data.HashMap.Strict as HashMap
import Data.Hashable(Hashable)
import qualified Data.List.PointedList as PL
import qualified Data.Map as Map
import qualified Data.Set as Set
import qualified Language.Haskell.TH.Syntax as THS
io :: MonadBase IO m => IO a -> m a
io = liftBase
fst3 :: (a,b,c) -> a
fst3 (x,_,_) = x
snd3 :: (a,b,c) -> b
snd3 (_,x,_) = x
trd3 :: (a,b,c) -> c
trd3 (_,_,x) = x
class SemiNum absolute relative | absolute -> relative where
(+~) :: absolute -> relative -> absolute
(-~) :: absolute -> relative -> absolute
(~-) :: absolute -> absolute -> relative
nubSet :: (Ord a) => [a] -> [a]
nubSet xss = f Set.empty xss
where
f _ [] = []
f s (x:xs) = if x `Set.member` s then f s xs else x : f (Set.insert x s) xs
mapAdjust' :: (Ord k) => (a -> a) -> k -> Map.Map k a -> Map.Map k a
mapAdjust' f = Map.alter f' where
f' Nothing = Nothing
f' (Just x) = let x' = f x in x' `seq` Just x'
mapFromFoldable :: (Foldable t, Ord k) => t (k, a) -> Map.Map k a
mapFromFoldable = foldMap (uncurry Map.singleton)
groupBy' :: (a -> a -> Bool) -> [a] -> [[a]]
groupBy' _ [] = []
groupBy' p l = s1 : groupBy' p s2 where
(s1, s2) = chain p l
chain :: (a -> a -> Bool) -> [a] -> ([a],[a])
chain _ [] = ([], [])
chain _ [e] = ([e], [])
chain q (e1 : es@(e2 : _))
| q e1 e2 = let (s1, s2) = chain q es in (e1 : s1, s2)
| otherwise = ([e1], es)
commonPrefix :: Eq a => [[a]] -> [a]
commonPrefix [] = []
commonPrefix strings
| any null strings = []
| all (== prefix) heads = prefix : commonPrefix tailz
| otherwise = []
where
(heads, tailz) = unzip [(h,t) | (h:t) <- strings]
prefix = head heads
findPL :: (a -> Bool) -> [a] -> Maybe (PL.PointedList a)
findPL p xs = go [] xs where
go _ [] = Nothing
go ls (f:rs) | p f = Just (PL.PointedList ls f rs)
| otherwise = go (f:ls) rs
swapFocus :: (PL.PointedList a -> PL.PointedList a) -> (PL.PointedList a -> PL.PointedList a)
swapFocus moveFocus xs =
let xs' = moveFocus xs
f1 = view PL.focus xs
f2 = view PL.focus xs'
in set PL.focus f1 . moveFocus . set PL.focus f2 $ xs
instance (Eq k, Hashable k, Binary k, Binary v) => Binary (HashMap.HashMap k v) where
put x = put (HashMap.toList x)
get = HashMap.fromList <$> get
makeClassyWithSuffix :: String -> THS.Name -> THS.Q [THS.Dec]
makeClassyWithSuffix s = makeLensesWith (classyRules
& lensField .~ (\_ n -> addSuffix n s)
& lensClass .~ classy)
where
classy :: THS.Name -> Maybe (THS.Name, THS.Name)
classy n = case THS.nameBase n of
x:xs -> Just (THS.mkName ("Has" ++ x:xs),
THS.mkName (toLower x : xs ++ s))
[] -> Nothing
addSuffix :: THS.Name -> String -> [DefName]
addSuffix n s = [TopName $ THS.mkName $ THS.nameBase n ++ s]
makeLensesWithSuffix :: String -> THS.Name -> THS.Q [THS.Dec]
makeLensesWithSuffix s =
makeLensesWith (defaultFieldRules & lensField .~ (\_ n -> addSuffix n s))