Skip to content

Instantly share code, notes, and snippets.

@gallais
Created September 15, 2016 00:33
Show Gist options
  • Save gallais/b769685806fd15d86c79cbdfa8a1982b to your computer and use it in GitHub Desktop.
Save gallais/b769685806fd15d86c79cbdfa8a1982b to your computer and use it in GitHub Desktop.
Focusing on each element individually and applying a function to the foci
{-# LANGUAGE RecordWildCards #-}
module AllContexts where
import Data.List
data Context a = Context
{ before :: [a]
, focus :: a
, after :: [a]
} deriving Show
inspect :: [a] -> Maybe (a, [a])
inspect [] = Nothing
inspect (x : xs) = Just (x, xs)
mkContext :: [a] -> Maybe (Context a)
mkContext = fmap (uncurry $ Context []) . inspect
moveRight :: Context a -> Maybe (Context a)
moveRight Context{..} = uncurry (Context (focus : before)) <$> inspect after
fromContext :: Context a -> [a]
fromContext Context{..} = reverse before ++ focus : after
allContexts :: [a] -> [Context a]
allContexts = unfoldr (fmap (\ s -> (s, moveRight s))) . mkContext
onFocus :: (a -> a) -> Context a -> Context a
onFocus f c = c { focus = f (focus c) }
applyMap :: (a -> a) -> [a] -> [[a]]
applyMap f = map (fromContext . onFocus f) . allContexts
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment