Last active
August 29, 2015 14:05
-
-
Save sordina/1ac0f8bc4e320e6a2fdf to your computer and use it in GitHub Desktop.
From the MHUG meetup on 28 August, 2014
This file contains hidden or bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
{-# LANGUAGE TemplateHaskell #-} | |
{-# OPTIONS_GHC -fno-warn-missing-signatures -fno-warn-type-defaults #-} | |
import Control.Lens | |
import Control.Monad.State | |
import Control.Arrow | |
import Data.Bits.Lens | |
import Data.Map | |
import Data.Word | |
{- Reference: https://github.com/ekmett/lens -} | |
-- view,views,^. use,uses View target(s). view works like use over a MonadReader | |
-- set, .~ <.~ .= assign,<.= Replace target(s). <<.~ and <<.= return the old value | |
-- over,mapOf,%~ <%~ %= <%= Update target(s). <<%~ and <<%= return the old value | |
-- id,traverseOf,%%~ %%= Update target(s) with an Applicative or auxiliary result | |
-- +~ <+~ += <+= Add to target(s) | |
-- -~ <-~ -= <-= Subtract from target(s) | |
-- *~ <*~ *= <*= Multiply target(s) | |
-- //~ <//~ //= <//= Divide target(s) | |
-- ^~ <^~ ^= <^= Raise target(s) to a non-negative Integral power | |
-- ^^~ <^^~ ^^= <^^= Raise target(s) to an Integral power | |
-- **~ <**~ **= <**= Raise target(s) to an arbitrary power | |
-- ||~ <||~ ||= <||= Logically or target(s) | |
-- &&~ <&&~ &&= <&&= Logically and target(s) | |
-- <>~ <<>~ <>= <<>= mappend to the target monoidal value(s) | |
-- headOf,^? Return Just the first target or Nothing | |
-- toListOf,^.. Return a list of the target(s) | |
-- perform,performs^! Perform monadic action(s) | |
-- | |
-- Control.Lens (Indexed) | |
-- | |
-- iover,imapOf,%@~ <%@~ %@= <%@= Update target(s) with access to the index. | |
-- withIndex,itraverseOf,%%@~ %%@= Update target(s) with an Applicative or auxiliary result with access to the index. | |
-- | |
-- Data.Bits.Lens | |
-- | |
-- .|.~ <.|.~ .|.= <.|.= Bitwise or target(s) | |
-- .&.~ <.&.~ .&.= <.&.= Bitwise and target(s) | |
-- | |
-- System.FilePath.Lens | |
-- | |
-- </>~ <</>~ </>= <</>= Append a relative path to a FilePath | |
-- <.>~ <<.>~ <.>= <<.>= Append a file extension to a FilePath | |
-- Random crap | |
data Foo a = F { _x :: a | |
, _y :: [ a ] | |
} | |
data Bar x = B { _asdf :: [x], _qwer :: (x,Int) } | |
makeLenses ''Foo | |
makeLenses ''Bar | |
myLensFooBar = view (asdf . traverse . x) | |
(B [F "a" ["hello"], F "b" ["world"]] (F "b" ["world"], 4)) | |
myData = F "hello" [ "world", "!" ] | |
firstWord = myData ^. x | |
firstWord' = view x myData | |
myOr = id .|.~ (2345 :: Int) $ (1234 :: Int) | |
myOr' = _3 .|.~ (2345 :: Int) $ ('a','b', (1234 :: Int)) | |
-- Examples from the Edward | |
-- view,views,^. use,uses View target(s). view works like use over a MonadReader | |
view_example_1 = view id ('a',2,"c") -- ('a',2,"c") | |
view_example_2 = view _2 ('a',2,"c") -- 2 | |
view_example_3 = view f (1,'b' ) where f = to snd -- 'b' | |
view_example_4 = ('a',2,"c") ^. id -- ('a',2,"c") | |
view_example_5 = ('a',2,"c") ^. _2 -- 2 | |
view_example_6 = (1,'b' ) ^. f where f = to snd -- 'b' | |
views_example_1 = views traverse snd [("a","b")] -- "b" | |
views_example_2 = views traverse snd [(1,"b"),(2,"c")] -- "bc" | |
use_example_1 = evalState (use _1) ('a',2) -- 'a' | |
use_example_2 = evalState (use (_1 . _2)) (('a',"b"),2) -- "b" | |
uses_example_1 = evalState (uses traverse snd) [(1,"a"),(2,"b")] -- "ab" | |
-- set, .~ <.~ .= assign,<.= Replace target(s). <<.~ and <<.= return the old value | |
set_example_1 = set _2 "testing" ('a',2,[44]) -- ('a',"testing",[44]) | |
set_example_2 = _2 .~ "testing" $ ('a',2,[44]) -- ('a',"testing",[44]) | |
set_example_3 = _3 <.~ "world" $ ("good","morning","vietnam") -- ("world", ("good","morning","world")) | |
set_example_4 = ("good","morning","vietnam") & _3 <.~ "world" -- ("world", ("good","morning","world")) | |
set_example_5 = execState (_1 .= 'c') ('a',2) -- ('c',2) | |
set_example_6 = execState (assign _1 'c') ('a',2) -- ('c',2) | |
set_example_7 = execState (assign both 'c') ('a','b') -- ('c','c') | |
set_example_8 = execState (assign both 'c') ('a','b','c') -- ('c','c','c') | |
set_example_9 = execState (assign traverse 'c') ['a'..'z'] -- replicate 26 'c' | |
set_example_10 = runState (_2 <.= 'x') ('a','b','c') -- ('x',('a','x','c')) | |
set_example_11 = _2 <<.~ 'x' $ ('a','b','c') -- ('b',('a','x','c')) | |
set_example_12 = runState (_2 <<.= 'x') ('a','b','c') -- ('b',('a','x','c')) | |
-- over,mapOf,%~ <%~ %= <%= Update target(s). <<%~ and <<%= return the old value | |
over_example_1 = over _1 succ (1,2,3) -- (2,2,3) | |
over_example_2 = over both succ (1,2,3) -- (1,3,4) ??? | |
over_example_3 = over traverse succ [1..10] -- [2..11] | |
-- mapOf is deprecated in favor of over | |
over_example_4 = _1 %~ succ $ (1,2,3) -- (2,2,3) | |
over_example_5 = both %~ succ $ (1,2,3) -- (1,3,4) | |
over_example_5b = each %~ succ $ (1,2,3) -- (2,3,4) | |
over_example_6 = traverse %~ succ $ [1..10] -- [2..11] | |
over_example_7 = _2 <%~ succ $ (1,2,3,4) -- (3,(1,3,3,4)) | |
over_example_8 = execState (_1 %= succ) (1,2) -- (2,2) | |
over_example_9 = runState (_1 <%= succ) (1,2) -- (2,(2,2)) | |
over_example_10 = _1 <<%~ succ $ (1,2) -- (1,(2,2)) | |
over_example_11 = runState (_1 <<%= succ) (1,2) -- (1,(2,2)) | |
-- id,traverseOf,%%~ %%= Update target(s) with an Applicative or auxiliary result | |
id_example_1 = set id "lol" (1,2,3,4) -- "lol" -- id is a lens! | |
id_example_2 = traverseOf id id "hello" -- "hello" | |
id_example_3 = traverseOf id (:[]) "hello" -- ["hello"] | |
id_example_4 = traverseOf each (:[]) ('a','b','c') -- [('a','b','c')] | |
id_example_5 = traverseOf each print ('a','b','c') -- >>> 'a' 'b' 'c'; ((),(),()) | |
id_example_6 = traverseOf each (:"de") ('a','b') -- [('a','b'),('a','d'),('a','e'),('d','b'),('d','d'),('d','e'),('e','b'),('e','d'),('e','e')] | |
id_example_7 = each (:"de") $ ('a','b') -- [('a','b'),('a','d'),('a','e'),('d','b'),('d','d'),('d','e'),('e','b'),('e','d'),('e','e')] | |
id_example_8 = each %%~ (:"de") $ ('a','b') -- [('a','b'),('a','d'),('a','e'),('d','b'),('d','d'),('d','e'),('e','b'),('e','d'),('e','e')] | |
id_example_9 = traverse %%~ (:"de") $ "ab" -- ["ab","ad","ae","db","dd","de","eb","ed","ee"] | |
id_example_10 = runState (_1 %%= (succ &&& pred)) (1,2) -- (2,(0,2)) -- ??? additional info? | |
add_example_1 = _2 +~ 4 $ (1,2) -- (1,6) | |
add_example_2 = _2 <+~ 4 $ (1,2) -- (6,(1,6)) | |
add_example_3 = runState (_2 += 4) (1,2) -- ((),(1,6)) | |
add_example_4 = runState (_2 <+= 4) (1,2) -- (6,(1,6)) | |
add_example_5 = runState (_2 <<+= 4) (1,2) -- (2,(1,6)) | |
subtract_example_1 = _2 -~ 4 $ (1,2) -- (1,-2) | |
subtract_example_2 = _2 <-~ 4 $ (1,2) -- (-2,(1,-2)) | |
subtract_example_3 = runState (_2 -= 4) (1,2) -- ((),(1,-2)) | |
subtract_example_4 = runState (_2 <-= 4) (1,2) -- (-2,(1,-2)) | |
subtract_example_5 = runState (_2 <<-= 4) (1,2) -- (2,(1,-2)) | |
-- +~ <+~ += <+= Add to target(s) | |
-- -~ <-~ -= <-= Subtract from target(s) | |
-- *~ <*~ *= <*= Multiply target(s) | |
-- //~ <//~ //= <//= Divide target(s) | |
-- ^~ <^~ ^= <^= Raise target(s) to a non-negative Integral power | |
-- ^^~ <^^~ ^^= <^^= Raise target(s) to an Integral power | |
-- **~ <**~ **= <**= Raise target(s) to an arbitrary power | |
-- ||~ <||~ ||= <||= Logically or target(s) | |
-- &&~ <&&~ &&= <&&= Logically and target(s) | |
-- <>~ <<>~ <>= <<>= mappend to the target monoidal value(s) | |
-- Multiply: * | |
-- Divide: // | |
-- Natural Power: ^ | |
-- Integer Power: ^^ | |
-- Power: ** | |
-- Logical Or: || | |
-- Logical And: && | |
-- Mappend: <> | |
-- headOf,^? Return Just the first target or Nothing | |
-- headOf => firstOf | |
first_example_1 = firstOf traverse [] -- Nothing | |
first_example_2 = firstOf traverse [1,2] -- Just 1 | |
first_example_3 = firstOf id [1,2] -- Just [1,2] | |
first_example_4 = firstOf each (1,2,3) -- Just 1 | |
first_example_5 = firstOf ignored (1,2,3) -- Nothing | |
first_example_6 = [] ^? traverse -- Nothing | |
first_example_7 = [1,2] ^? traverse -- Just 1 | |
first_example_8 = [1,2] ^? id -- Just [1,2] | |
first_example_9 = (1,2,3) ^? each -- Just 1 | |
first_example_10 = (1,2,3) ^? ignored -- Nothing | |
-- toListOf,^.. Return a list of the target(s) | |
list_example_1 = toListOf each $ (1,2,3) -- [1,2,3] | |
list_example_2 = (1,2,3) ^.. each -- [1,2,3] | |
-- perform,performs^! Perform monadic action(s) | |
perform_example_1 :: [[Int]] | |
perform_example_1 = perform each ([1,2],[3,4]) -- [[1,2,3,4]] | |
-- performs ??? | |
perform_example_2 = ["hello","world"] ^! traverse . act print -- >>> "hello" "world"; () | |
-- Control.Lens (Indexed) | |
-- http://ekmett.github.io/lens/Control-Lens-Setter.html#v:iover | |
-- TODO: Do the indexed ones later | |
-- iover,imapOf,%@~ <%@~ %@= <%@= Update target(s) with access to the index. | |
-- withIndex,itraverseOf,%%@~ %%@= Update target(s) with an Applicative or auxiliary result with access to the index. | |
-- Data.Bits.Lens | |
-- | |
-- .|.~ <.|.~ .|.= <.|.= Bitwise or target(s) | |
-- .&.~ <.&.~ .&.= <.&.= Bitwise and target(s) | |
bits_example_1_or = id .|.~ (1234 :: Word) $ (2345 :: Word) -- 3579 | |
bits_example_2_and = id .&.~ (1234 :: Word) $ (2345 :: Word) -- 0 | |
bits_example_3_and = id .&.~ (1234 :: Word) $ (1345 :: Word) -- 1088 | |
at_example = set (at 2) (Just True) (fromList $ zip [1..] [False, False, False]) -- Data.Map.fromList [(1,False),(2,True),(3,False)] | |
list_of_example_1 = toListOf bits (123 :: Word8) -- [True ,True ,False,True,True ,True,True,False] | |
list_of_example_2 = toListOf bits (234 :: Word8) -- [False,True ,False,True,False,True,True,True] | |
list_of_example_3 = toListOf bits (id .&.~ (123 :: Word8) $ (124 :: Word8)) -- [False,False,False,True,True ,True,True,False] | |
-- | |
-- System.FilePath.Lens | |
-- | |
-- </>~ <</>~ </>= <</>= Append a relative path to a FilePath | |
-- <.>~ <<.>~ <.>= <<.>= Append a file extension to a FilePath | |
iover_example = iover traversed (\a b -> (a + b) `mod` 7) [1..10] -- [1,3,5,0,2,4,6,1,3,5] |
Sign up for free
to join this conversation on GitHub.
Already have an account?
Sign in to comment