diff --git a/traversal.ipynb b/traversal.ipynb new file mode 100644 index 0000000..4188421 --- /dev/null +++ b/traversal.ipynb @@ -0,0 +1,3088 @@ +{ + "cells": [ + { + "cell_type": "code", + "execution_count": 93, + "metadata": {}, + "outputs": [ + { + "data": { + "text/html": [ + "
Unused LANGUAGE pragma
Found:
{-# LANGUAGE TemplateHaskell #-}
Why Not:
Unused LANGUAGE pragma
Found:
{-# LANGUAGE TypeApplications #-}
Why Not:
Unused LANGUAGE pragma
Found:
{-# LANGUAGE OverloadedStrings #-}
Why Not:
" + ], + "text/plain": [ + "Line 1: Unused LANGUAGE pragma\n", + "Found:\n", + "{-# LANGUAGE TemplateHaskell #-}\n", + "Why not:\n", + "Line 6: Unused LANGUAGE pragma\n", + "Found:\n", + "{-# LANGUAGE TypeApplications #-}\n", + "Why not:\n", + "Line 9: Unused LANGUAGE pragma\n", + "Found:\n", + "{-# LANGUAGE OverloadedStrings #-}\n", + "Why not:" + ] + }, + "metadata": {}, + "output_type": "display_data" + } + ], + "source": [ + "{-# LANGUAGE TemplateHaskell #-}\n", + "{-# LANGUAGE FlexibleInstances #-}\n", + "{-# LANGUAGE FlexibleContexts #-}\n", + "{-# LANGUAGE RankNTypes #-}\n", + "{-# LANGUAGE ScopedTypeVariables #-}\n", + "{-# LANGUAGE TypeApplications #-}\n", + "{-# LANGUAGE TypeFamilies #-}\n", + "{-# LANGUAGE InstanceSigs #-}\n", + "{-# LANGUAGE OverloadedStrings #-}\n", + "{-# LANGUAGE AllowAmbiguousTypes #-}\n", + "\n", + "import Control.Lens\n", + "import Numeric.Lens\n", + "import Data.Bits.Lens\n", + "import Data.Data.Lens\n", + "\n", + "import Control.Applicative\n", + "import Data.Char as C\n", + "import qualified Data.Map as M\n", + "import qualified Data.Set as S\n", + "import qualified Data.Text as T\n", + "import qualified Data.List as L" + ] + }, + { + "cell_type": "code", + "execution_count": 9, + "metadata": {}, + "outputs": [ + { + "data": { + "text/html": [ + "both :: forall (r :: * -> * -> *) (f :: * -> *) a b. (Bitraversable r, Applicative f) => (a -> f b) -> r a a -> f (r b b)" + ], + "text/plain": [ + "both :: forall (r :: * -> * -> *) (f :: * -> *) a b. (Bitraversable r, Applicative f) => (a -> f b) -> r a a -> f (r b b)" + ] + }, + "metadata": {}, + "output_type": "display_data" + }, + { + "data": { + "text/plain": [ + "[\"Bubbles\",\"Buttercup\"]" + ] + }, + "metadata": {}, + "output_type": "display_data" + }, + { + "data": { + "text/plain": [ + "(\"Bubbles!\",\"Buttercup!\")" + ] + }, + "metadata": {}, + "output_type": "display_data" + }, + { + "data": { + "text/plain": [ + "(\"Blossom\",\"Blossom\")" + ] + }, + "metadata": {}, + "output_type": "display_data" + }, + { + "data": { + "text/plain": [ + "(7,9)" + ] + }, + "metadata": {}, + "output_type": "display_data" + }, + { + "data": { + "text/plain": [ + "(10,20,30)" + ] + }, + "metadata": {}, + "output_type": "display_data" + }, + { + "data": { + "text/plain": [ + "[10,20,30]" + ] + }, + "metadata": {}, + "output_type": "display_data" + }, + { + "data": { + "text/plain": [ + "\"HERE'S JOHNNY\"" + ] + }, + "metadata": {}, + "output_type": "display_data" + }, + { + "ename": "", + "evalue": "", + "output_type": "error", + "traceback": [ + ":1:43: error:\n • Couldn't match type ‘Int’ with ‘Char’ arising from a use of ‘each’\n • In the first argument of ‘(.~)’, namely ‘each’\n In the second argument of ‘(&)’, namely ‘each .~ (22 :: Int)’\n In the expression: (\"Houston we have a problem\" :: T.Text) & each .~ (22 :: Int)" + ] + } + ], + "source": [ + "-- both is a traversal which focuses both sides of a tuple if it has the same type in each side\n", + "\n", + "-- Specialized to tuples\n", + "-- both :: Traversal (a, a) (b, b) a b\n", + "\n", + "-- General\n", + "-- both :: Bitraversable r => Traversal (r a a) (r b b) a b\n", + "\n", + ":t both\n", + "\n", + "(\"Bubbles\", \"Buttercup\") ^.. both\n", + "\n", + "(\"Bubbles\", \"Buttercup\") & both %~ (++ \"!\")\n", + "\n", + "(\"Bubbles\", \"Buttercup\") & both .~ \"Blossom\"\n", + "\n", + "(\"Bubbles\", \"Buttercup\") & both %~ length\n", + "\n", + "(1, 2, 3) & each %~ (*10)\n", + "\n", + "[1, 2, 3] & each %~ (*10)\n", + "\n", + "(\"Here's Johnny\" :: T.Text) & each %~ C.toUpper\n", + "\n", + "(\"Houston we have a problem\" :: T.Text) & each .~ (22 :: Int)" + ] + }, + { + "cell_type": "code", + "execution_count": 13, + "metadata": {}, + "outputs": [ + { + "data": { + "text/plain": [ + "[10,20,30,4,5]" + ] + }, + "metadata": {}, + "output_type": "display_data" + }, + { + "data": { + "text/plain": [ + "[1,2,3,40,50]" + ] + }, + "metadata": {}, + "output_type": "display_data" + }, + { + "data": { + "text/plain": [ + "\"ONCE UPON A TIME - optics became mainstream\"" + ] + }, + "metadata": {}, + "output_type": "display_data" + }, + { + "data": { + "text/plain": [ + "[1,20,3,40,5]" + ] + }, + "metadata": {}, + "output_type": "display_data" + }, + { + "data": { + "text/plain": [ + "(\"short\",\"gnol yllaer\")" + ] + }, + "metadata": {}, + "output_type": "display_data" + } + ], + "source": [ + "[1, 2, 3, 4, 5] & taking 3 traversed *~ 10\n", + "\n", + "[1, 2, 3, 4, 5] & dropping 3 traversed *~ 10\n", + "\n", + "-- focus characters until '-'\n", + "\"once upon a time - optics became mainstream\" & takingWhile (/= '-') traversed %~ toUpper\n", + "\n", + "-- filter can be used to filter focuses from a traversal\n", + "\n", + "-- Multiply all even numbers by 10\n", + "[1, 2, 3, 4, 5] & traversed . filtered even *~ 10\n", + "\n", + "-- Reverse only the long strings\n", + "(\"short\", \"really long\") & both . filtered ((> 5) . length) %~ reverse" + ] + }, + { + "cell_type": "markdown", + "metadata": {}, + "source": [ + "### Traversal Combinators" + ] + }, + { + "cell_type": "code", + "execution_count": 23, + "metadata": {}, + "outputs": [ + { + "data": { + "text/html": [ + "traversed :: forall (p :: * -> * -> *) (f1 :: * -> *) (f2 :: * -> *) a b. (Indexable Int p, Traversable f1, Applicative f2) => p a (f2 b) -> f1 a -> f2 (f1 b)" + ], + "text/plain": [ + "traversed :: forall (p :: * -> * -> *) (f1 :: * -> *) (f2 :: * -> *) a b. (Indexable Int p, Traversable f1, Applicative f2) => p a (f2 b) -> f1 a -> f2 (f1 b)" + ] + }, + "metadata": {}, + "output_type": "display_data" + }, + { + "data": { + "text/plain": [ + "[10,20,30]" + ] + }, + "metadata": {}, + "output_type": "display_data" + }, + { + "data": { + "text/plain": [ + "(\"Batman\",\"Sup\")" + ] + }, + "metadata": {}, + "output_type": "display_data" + }, + { + "data": { + "text/plain": [ + "fromList [(\"Gohan\",\"710\"),(\"Goku\",\"Over 9000\"),(\"Krillin\",\"5000\"),(\"Piccolo\",\"408\")]" + ] + }, + "metadata": {}, + "output_type": "display_data" + }, + { + "data": { + "text/plain": [ + "Node {rootLabel = \"sneL\", subForest = [Node {rootLabel = \"dloF\", subForest = []},Node {rootLabel = \"lasrevarT\", subForest = []}]}" + ] + }, + "metadata": {}, + "output_type": "display_data" + } + ], + "source": [ + "-- Errors out\n", + "-- [1, 2, 3] & folded %~ (*10)\n", + "\n", + "-- Simplified\n", + "-- traversed :: Traversable f => Traversal (f a) (f b) a b\n", + "\n", + "-- A bit more complex\n", + "-- traversed :: Traversable f => IndexedTraversal Int (f a) (f b) a b\n", + "\n", + "-- Actual\n", + ":t traversed\n", + "\n", + "[1, 2, 3] & traversed *~ 10\n", + "\n", + "-- Tuples are traversable over their last slot\n", + "(\"Batman\", \"Superman\") & traversed %~ take 3\n", + "\n", + "let powerLevels = M.fromList [ (\"Gohan\", 710), (\"Goku\", 9001), (\"Krillin\", 5000), (\"Piccolo\", 408) ]\n", + "\n", + "powerLevels & traversed %~ \\n -> if n > 9000 then \"Over 9000\" else show n\n", + "\n", + "import Data.Tree\n", + "\n", + "let opticsTree = Node \"Lens\" [Node \"Fold\" [], Node \"Traversal\" []]\n", + "\n", + "opticsTree & traversed %~ reverse" + ] + }, + { + "cell_type": "markdown", + "metadata": {}, + "source": [ + "### More Combinators" + ] + }, + { + "cell_type": "code", + "execution_count": 30, + "metadata": {}, + "outputs": [ + { + "data": { + "text/html": [ + "worded :: forall (p :: * -> * -> *) (f :: * -> *). (Indexable Int p, Applicative f) => p String (f String) -> String -> f String" + ], + "text/plain": [ + "worded :: forall (p :: * -> * -> *) (f :: * -> *). (Indexable Int p, Applicative f) => p String (f String) -> String -> f String" + ] + }, + "metadata": {}, + "output_type": "display_data" + }, + { + "data": { + "text/html": [ + "lined :: forall (p :: * -> * -> *) (f :: * -> *). (Indexable Int p, Applicative f) => p String (f String) -> String -> f String" + ], + "text/plain": [ + "lined :: forall (p :: * -> * -> *) (f :: * -> *). (Indexable Int p, Applicative f) => p String (f String) -> String -> f String" + ] + }, + "metadata": {}, + "output_type": "display_data" + }, + { + "data": { + "text/plain": [ + "[\"I'll\",\"be\",\"back!\"]" + ] + }, + "metadata": {}, + "output_type": "display_data" + }, + { + "data": { + "text/plain": [ + "[\"Run\",\"Forrest\",\"Run\"]" + ] + }, + "metadata": {}, + "output_type": "display_data" + }, + { + "data": { + "text/plain": [ + "\"*blue* *suede* *shoes*\"" + ] + }, + "metadata": {}, + "output_type": "display_data" + }, + { + "data": { + "text/plain": [ + "\"Blue Suede Shoes\"" + ] + }, + "metadata": {}, + "output_type": "display_data" + }, + { + "data": { + "text/plain": [ + "\"#blue\\n#suede\\n#shoes\"" + ] + }, + "metadata": {}, + "output_type": "display_data" + }, + { + "data": { + "text/plain": [ + "\"blue suede shoes\"" + ] + }, + "metadata": {}, + "output_type": "display_data" + } + ], + "source": [ + "-- worded :: Traversal' String String\n", + "-- lined :: Traversal' String String\n", + "\n", + ":t worded\n", + ":t lined\n", + "\n", + "\"I'll be back!\" ^.. worded\n", + "\n", + "\"Run\\nForrest\\nRun\" ^.. lined\n", + "\n", + "-- Surround each word with '*'s\n", + "\"blue suede shoes\" & worded %~ \\s -> \"*\" ++ s ++ \"*\"\n", + "\n", + "-- Capitalize each word\n", + "\"blue suede shoes\" & worded %~ \\(x:xs) -> C.toUpper x : xs\n", + "\n", + "-- Add a \"#\" to the start of each line:\n", + "\"blue\\nsuede\\nshoes\" & lined %~ ('#':)\n", + "\n", + "-- Mapping the identity function still has the\n", + "-- white-space collapsing side-effects of `unwords`\n", + "\"blue \\n suede \\n \\n shoes\" & worded %~ id" + ] + }, + { + "cell_type": "markdown", + "metadata": {}, + "source": [ + "### Traversing multiple paths at once" + ] + }, + { + "cell_type": "code", + "execution_count": 42, + "metadata": {}, + "outputs": [ + { + "data": { + "text/plain": [ + "[\"T-Rex\",\"Stegosaurus\"]" + ] + }, + "metadata": {}, + "output_type": "display_data" + }, + { + "data": { + "text/plain": [ + "[1,2,3,4,5,6,7]" + ] + }, + "metadata": {}, + "output_type": "display_data" + }, + { + "data": { + "text/plain": [ + "[\"T-Rex\",\"Ankylosaurus\",\"Stegosaurus\"]" + ] + }, + "metadata": {}, + "output_type": "display_data" + }, + { + "data": { + "text/plain": [ + "(\"COWABUNGA\",[\"LET'S\",\"ORDER\",\"PIZZA\"])" + ] + }, + "metadata": {}, + "output_type": "display_data" + }, + { + "data": { + "text/plain": [ + "Left (-1,-2)" + ] + }, + "metadata": {}, + "output_type": "display_data" + }, + { + "data": { + "text/plain": [ + "Right [-3,-4]" + ] + }, + "metadata": {}, + "output_type": "display_data" + } + ], + "source": [ + "-- beside :: Traversal s t a b -> Traversal s' t' a b -> Traversal (s, s') (t, t') a b\n", + "\n", + "-- beside :: Lens s t a b -> Lens s' t' a b -> Traversal (s, s') (t, t') a b\n", + "-- beside :: Fold s a -> Fold s' a -> Fold (s, s') a\n", + "\n", + "let dinos = (\"T-Rex\", (42, \"Stegosaurus\"))\n", + "\n", + "dinos ^.. beside id _2\n", + "\n", + "let numbers = ([(1, 2), (3, 4)], [5, 6, 7])\n", + "\n", + "numbers ^.. beside (traversed . both) traversed\n", + "\n", + "(\"T-Rex\", (\"Ankylosaurus\", \"Stegosaurus\")) ^.. beside id both\n", + "\n", + "-- both = beside id id\n", + "\n", + "-- We can modify all characters inside both halves of the tuple\n", + "(\"Cowabunga\", [\"let's\", \"order\", \"pizza\"])\n", + " -- Each half of the tuple has a different path to focus the characters\n", + " & beside traversed (traversed . traversed)\n", + " %~ toUpper\n", + " \n", + "-- beside both traversed :: Traversal' (Either (Int, Int) [Int]) Int\n", + "Left (1, 2) & beside both traversed %~ negate\n", + "\n", + "Right [3, 4] & beside both traversed %~ negate :: Either (Int, Int) [Int]" + ] + }, + { + "cell_type": "markdown", + "metadata": {}, + "source": [ + "### Focusing a specific traversal element" + ] + }, + { + "cell_type": "code", + "execution_count": 44, + "metadata": {}, + "outputs": [ + { + "data": { + "text/html": [ + "element :: forall (p :: * -> * -> *) (t :: * -> *) (f :: * -> *) a. (Indexable Int p, Traversable t, Applicative f) => Int -> p a (f a) -> t a -> f (t a)" + ], + "text/plain": [ + "element :: forall (p :: * -> * -> *) (t :: * -> *) (f :: * -> *) a. (Indexable Int p, Traversable t, Applicative f) => Int -> p a (f a) -> t a -> f (t a)" + ] + }, + "metadata": {}, + "output_type": "display_data" + }, + { + "data": { + "text/plain": [ + "Just 2" + ] + }, + "metadata": {}, + "output_type": "display_data" + }, + { + "data": { + "text/plain": [ + "[0,1,200,3,4]" + ] + }, + "metadata": {}, + "output_type": "display_data" + } + ], + "source": [ + "-- element :: Traversable f => Int -> Traversal' (f a) a\n", + "\n", + ":t element\n", + "\n", + "[0, 1, 2, 3, 4] ^? element 2\n", + "\n", + "[0, 1, 2, 3, 4] & element 2 *~ 100\n", + "\n", + "-- elementOf :: Traversal' s a -> Int -> Traversal' s a\n", + "-- elementOf :: Fold s a -> Int -> Fold s a\n", + "\n", + "-- `element` is basically `elementOf traversed`\n", + "[0, 1, 2, 3, 4] ^? elementOf traversed 2\n", + "\n", + "-- We can get a specific element from a composition of traversals\n", + "[[0, 1, 2], [3, 4], [5, 6, 7, 8]] ^? elementOf (traversed . traversed) 6\n", + "\n", + "-- Modify the 6th integer from within nested lists:\n", + "[[0, 1, 2], [3, 4], [5, 6, 7, 8]]\n", + " & elementOf (traversed . traversed) 6 *~ 100" + ] + }, + { + "cell_type": "markdown", + "metadata": {}, + "source": [ + "### Composing Traversals" + ] + }, + { + "cell_type": "code", + "execution_count": 47, + "metadata": {}, + "outputs": [ + { + "data": { + "text/plain": [ + "\"Blue Suede Shoes\"" + ] + }, + "metadata": {}, + "output_type": "display_data" + }, + { + "data": { + "text/plain": [ + "[\"short\",\"*really* *long*\"]" + ] + }, + "metadata": {}, + "output_type": "display_data" + }, + { + "data": { + "text/plain": [ + "((\"Rich Ritchie\",100000),(\"Archie\",32),(\"Rich Reggie\",4350))" + ] + }, + "metadata": {}, + "output_type": "display_data" + } + ], + "source": [ + "-- Capitalize the first char of every word\n", + "\"blue suede shoes\" & worded . taking 1 traversed %~ toUpper\n", + "\n", + "-- Find all strings longer than 5 chars\n", + "-- then surround each word in that string with '*'\n", + "[\"short\", \"really long\"]\n", + " & traversed\n", + " . filtered ((> 5) . length)\n", + " . worded\n", + " %~ \\s -> \"*\" ++ s ++ \"*\"\n", + " \n", + "-- Add \"Rich \" to the names of people with more than $1000\n", + "((\"Ritchie\", 100000), (\"Archie\", 32), (\"Reggie\", 4350))\n", + " & each\n", + " . filtered ((> 1000) . snd)\n", + " . _1\n", + " %~ (\"Rich \" ++)" + ] + }, + { + "cell_type": "markdown", + "metadata": {}, + "source": [ + "### Exercises - Simple Traversals" + ] + }, + { + "cell_type": "code", + "execution_count": 67, + "metadata": {}, + "outputs": [ + { + "data": { + "text/plain": [ + "(\"N/A\",\"N/A\")" + ] + }, + "metadata": {}, + "output_type": "display_data" + }, + { + "data": { + "text/plain": [ + "(\"xxxxxxxx\",\"xxxx\")" + ] + }, + "metadata": {}, + "output_type": "display_data" + }, + { + "data": { + "text/plain": [ + "(\"Mal\",[\"Kay\",\"Ina\",\"Jay\"])" + ] + }, + "metadata": {}, + "output_type": "display_data" + }, + { + "data": { + "text/plain": [ + "(\"Malcolm\",[\"Kaylee\",\"River\",\"Jayne\"])" + ] + }, + "metadata": {}, + "output_type": "display_data" + }, + { + "data": { + "text/plain": [ + "[\"Die xxxxxxx Day\",\"Live xxx Let Die\",\"You xxxx Live Twice\"]" + ] + }, + "metadata": {}, + "output_type": "display_data" + }, + { + "data": { + "text/html": [ + "each :: forall s t a b (f :: * -> *). (Each s t a b, Applicative f) => (a -> f b) -> s -> f t" + ], + "text/plain": [ + "each :: forall s t a b (f :: * -> *). (Each s t a b, Applicative f) => (a -> f b) -> s -> f t" + ] + }, + "metadata": {}, + "output_type": "display_data" + }, + { + "data": { + "text/html": [ + "traversed :: forall (p :: * -> * -> *) (f1 :: * -> *) (f2 :: * -> *) a b. (Indexable Int p, Traversable f1, Applicative f2) => p a (f2 b) -> f1 a -> f2 (f1 b)" + ], + "text/plain": [ + "traversed :: forall (p :: * -> * -> *) (f1 :: * -> *) (f2 :: * -> *) a b. (Indexable Int p, Traversable f1, Applicative f2) => p a (f2 b) -> f1 a -> f2 (f1 b)" + ] + }, + "metadata": {}, + "output_type": "display_data" + }, + { + "data": { + "text/plain": [ + "((True,\"STRAWberries\"),(False,\"Blueberries\"),(True,\"BLACKberries\"))" + ] + }, + "metadata": {}, + "output_type": "display_data" + }, + { + "data": { + "text/plain": [ + "(\"Strawberries\",\"Blueberries\",\"Blackberries\")" + ] + }, + "metadata": {}, + "output_type": "display_data" + } + ], + "source": [ + "-- 1.\n", + "\n", + "-- What type of optic do you get when you compose a traversal with a fold?\n", + "-- We get a fold\n", + "\n", + "-- Which of the optics we have learned can act as a traversal?\n", + "-- Lens or Traversal\n", + "\n", + "-- Which of the optics we have learned can act as a fold?\n", + "-- Lens, traversal and fold\n", + "\n", + "-- 2.\n", + "-- Fill in the blank to complete each expression:\n", + "\n", + "(\"Jurassic\", \"Park\") & each .~ \"N/A\"\n", + "\n", + "(\"Jurassic\", \"Park\") & both . traversed .~ 'x'\n", + "\n", + "(\"Malcolm\", [\"Kaylee\", \"Inara\", \"Jayne\"])\n", + " & beside id traversed %~ take 3\n", + "\n", + "(\"Malcolm\", [\"Kaylee\", \"Inara\", \"Jayne\"])\n", + " & _2 . element 1 .~ \"River\"\n", + "\n", + "[\"Die Another Day\", \"Live and Let Die\", \"You Only Live Twice\"]\n", + " & traversed . elementOf worded 1 . traversed .~ 'x'\n", + "\n", + ":t each\n", + ":t traversed\n", + "\n", + "((True, \"Strawberries\"), (False, \"Blueberries\"), (True, \"Blackberries\")) \n", + " & each . filtered fst . _2 . taking 5 traversed %~ C.toUpper\n", + " \n", + "((True, \"Strawberries\"), (False, \"Blueberries\"), (True, \"Blackberries\"))\n", + " & each %~ snd" + ] + }, + { + "cell_type": "markdown", + "metadata": {}, + "source": [ + "### Traversal Actions" + ] + }, + { + "cell_type": "code", + "execution_count": 75, + "metadata": {}, + "outputs": [ + { + "data": { + "text/html": [ + "sequenceA :: forall (t :: * -> *) (f :: * -> *) a. (Traversable t, Applicative f) => t (f a) -> f (t a)" + ], + "text/plain": [ + "sequenceA :: forall (t :: * -> *) (f :: * -> *) a. (Traversable t, Applicative f) => t (f a) -> f (t a)" + ] + }, + "metadata": {}, + "output_type": "display_data" + }, + { + "data": { + "text/plain": [ + "Just [1,2,3]" + ] + }, + "metadata": {}, + "output_type": "display_data" + }, + { + "data": { + "text/plain": [ + "Nothing" + ] + }, + "metadata": {}, + "output_type": "display_data" + }, + { + "data": { + "text/plain": [ + "Left \"Whoops\"" + ] + }, + "metadata": {}, + "output_type": "display_data" + }, + { + "data": { + "text/plain": [ + "[1,2,3]" + ] + }, + "metadata": {}, + "output_type": "display_data" + }, + { + "data": { + "text/html": [ + "traverse :: forall (t :: * -> *) (f :: * -> *) a b. (Traversable t, Applicative f) => (a -> f b) -> t a -> f (t b)" + ], + "text/plain": [ + "traverse :: forall (t :: * -> *) (f :: * -> *) a b. (Traversable t, Applicative f) => (a -> f b) -> t a -> f (t b)" + ] + }, + "metadata": {}, + "output_type": "display_data" + }, + { + "data": { + "text/html": [ + "readMaybe :: forall a. Read a => String -> Maybe a" + ], + "text/plain": [ + "readMaybe :: forall a. Read a => String -> Maybe a" + ] + }, + "metadata": {}, + "output_type": "display_data" + }, + { + "data": { + "text/plain": [ + "Just [1,2,3]" + ] + }, + "metadata": {}, + "output_type": "display_data" + }, + { + "data": { + "text/plain": [ + "Nothing" + ] + }, + "metadata": {}, + "output_type": "display_data" + }, + { + "data": { + "text/html": [ + "readFile :: FilePath -> IO String" + ], + "text/plain": [ + "readFile :: FilePath -> IO String" + ] + }, + "metadata": {}, + "output_type": "display_data" + }, + { + "data": { + "text/html": [ + "results :: IO [String]" + ], + "text/plain": [ + "results :: IO [String]" + ] + }, + "metadata": {}, + "output_type": "display_data" + }, + { + "data": { + "text/plain": [ + "[(\"a\",100),(\"a\",1000)]" + ] + }, + "metadata": {}, + "output_type": "display_data" + } + ], + "source": [ + ":t sequenceA\n", + "\n", + "\n", + "sequenceA [Just 1, Just 2, Just 3]\n", + "\n", + "sequenceA [Just 1, Nothing, Just 3]\n", + "\n", + "sequenceA $ Just (Left \"Whoops\")\n", + "\n", + "sequenceA ([pure 1, pure 2, pure 3] :: [IO Int]) >>= print\n", + "\n", + ":t traverse\n", + "\n", + "import Text.Read (readMaybe)\n", + "\n", + ":t readMaybe\n", + "\n", + "traverse readMaybe [\"1\", \"2\", \"3\"] :: Maybe [Int]\n", + "\n", + "traverse readMaybe [\"1\", \"snark\", \"3\"] :: Maybe [Int]\n", + "\n", + ":t readFile\n", + "\n", + "let results = traverse readFile [\"file1.txt\", \"file2.txt\"]\n", + "\n", + ":t results\n", + "\n", + "traverse (\\n -> [n * 10, n * 100]) (\"a\", 10)" + ] + }, + { + "cell_type": "markdown", + "metadata": {}, + "source": [ + "### Traverse on Traversals" + ] + }, + { + "cell_type": "code", + "execution_count": 81, + "metadata": {}, + "outputs": [ + { + "data": { + "text/html": [ + "traverse :: forall (t :: * -> *) (f :: * -> *) a b. (Traversable t, Applicative f) => (a -> f b) -> t a -> f (t b)" + ], + "text/plain": [ + "traverse :: forall (t :: * -> *) (f :: * -> *) a b. (Traversable t, Applicative f) => (a -> f b) -> t a -> f (t b)" + ] + }, + "metadata": {}, + "output_type": "display_data" + }, + { + "data": { + "text/html": [ + "traverseOf :: forall (f :: * -> *) s t a b. LensLike f s t a b -> (a -> f b) -> s -> f t" + ], + "text/plain": [ + "traverseOf :: forall (f :: * -> *) s t a b. LensLike f s t a b -> (a -> f b) -> s -> f t" + ] + }, + "metadata": {}, + "output_type": "display_data" + }, + { + "data": { + "text/html": [ + "traverseOf traversed :: forall (f1 :: * -> *) (f2 :: * -> *) a b. (Traversable f1, Applicative f2) => (a -> f2 b) -> f1 a -> f2 (f1 b)" + ], + "text/plain": [ + "traverseOf traversed :: forall (f1 :: * -> *) (f2 :: * -> *) a b. (Traversable f1, Applicative f2) => (a -> f2 b) -> f1 a -> f2 (f1 b)" + ] + }, + "metadata": {}, + "output_type": "display_data" + }, + { + "data": { + "text/plain": [ + "Just (1,2)" + ] + }, + "metadata": {}, + "output_type": "display_data" + }, + { + "data": { + "text/plain": [ + "Nothing" + ] + }, + "metadata": {}, + "output_type": "display_data" + }, + { + "data": { + "text/plain": [ + "[('a','b'),('a','B'),('A','b'),('A','B')]" + ] + }, + "metadata": {}, + "output_type": "display_data" + }, + { + "data": { + "text/plain": [ + "[(\"ab\",\"cd\"),(\"ab\",\"cD\"),(\"ab\",\"Cd\"),(\"ab\",\"CD\"),(\"aB\",\"cd\"),(\"aB\",\"cD\"),(\"aB\",\"Cd\"),(\"aB\",\"CD\"),(\"Ab\",\"cd\"),(\"Ab\",\"cD\"),(\"Ab\",\"Cd\"),(\"Ab\",\"CD\"),(\"AB\",\"cd\"),(\"AB\",\"cD\"),(\"AB\",\"Cd\"),(\"AB\",\"CD\")]" + ] + }, + "metadata": {}, + "output_type": "display_data" + } + ], + "source": [ + "-- Specialized signature\n", + "-- traverseOf :: Traversal s t a b -> (a -> f b) -> s -> f t\n", + "\n", + "-- Real signature\n", + "-- traverseOf :: LensLike f s t a b -> (a -> f b) -> s -> f t\n", + "\n", + ":t traverse\n", + ":t traverseOf\n", + ":t traverseOf traversed\n", + "\n", + "traverseOf both readMaybe (\"1\", \"2\") :: Maybe (Int, Int)\n", + "\n", + "traverseOf both readMaybe (\"not a number\", \"2\") :: Maybe (Int, Int)\n", + "\n", + "traverseOf both (\\c -> [toLower c, toUpper c]) ('a', 'b')\n", + "\n", + "traverseOf\n", + " (both . traversed)\n", + " (\\c -> [toLower c, toUpper c])\n", + " (\"ab\", \"cd\")" + ] + }, + { + "cell_type": "code", + "execution_count": 88, + "metadata": {}, + "outputs": [ + { + "data": { + "text/plain": [ + "Right [(\"Mike\",\"mike@tmnt.io\"),(\"Raph\",\"raph@tmnt.io\"),(\"Don\",\"don@tmnt.io\"),(\"Leo\",\"leo@tmnt.io\")]" + ] + }, + "metadata": {}, + "output_type": "display_data" + }, + { + "data": { + "text/plain": [ + "Left \"missing '@': raph.io\"" + ] + }, + "metadata": {}, + "output_type": "display_data" + }, + { + "data": { + "text/html": [ + "forOf :: forall (f :: * -> *) s t a b. LensLike f s t a b -> s -> (a -> f b) -> f t" + ], + "text/plain": [ + "forOf :: forall (f :: * -> *) s t a b. LensLike f s t a b -> s -> (a -> f b) -> f t" + ] + }, + "metadata": {}, + "output_type": "display_data" + }, + { + "data": { + "text/html": [ + "sequenceAOf :: forall (f :: * -> *) s t b. LensLike f s t (f b) b -> s -> f t" + ], + "text/plain": [ + "sequenceAOf :: forall (f :: * -> *) s t b. LensLike f s t (f b) b -> s -> f t" + ] + }, + "metadata": {}, + "output_type": "display_data" + }, + { + "data": { + "text/plain": [ + "Just (\"Garfield\",\"Lasagna\")" + ] + }, + "metadata": {}, + "output_type": "display_data" + }, + { + "data": { + "text/plain": [ + "Nothing" + ] + }, + "metadata": {}, + "output_type": "display_data" + }, + { + "data": { + "text/plain": [ + "Just ([\"apples\"],[\"oranges\"])" + ] + }, + "metadata": {}, + "output_type": "display_data" + }, + { + "data": { + "text/plain": [ + "Nothing" + ] + }, + "metadata": {}, + "output_type": "display_data" + } + ], + "source": [ + "validateEmail :: String -> Either String String\n", + "validateEmail email | elem '@' email = Right email\n", + " | otherwise = Left (\"missing '@': \" <> email)\n", + " \n", + "traverseOf (traversed . _2) validateEmail\n", + " [ (\"Mike\", \"mike@tmnt.io\")\n", + " , (\"Raph\", \"raph@tmnt.io\")\n", + " , (\"Don\", \"don@tmnt.io\")\n", + " , (\"Leo\", \"leo@tmnt.io\")\n", + " ]\n", + " \n", + "traverseOf (traversed . _2) validateEmail\n", + " [ (\"Mike\", \"mike@tmnt.io\")\n", + " , (\"Raph\", \"raph.io\")\n", + " , (\"Don\", \"don@tmnt.io\")\n", + " , (\"Leo\", \"leo@tmnt.io\")\n", + " ]\n", + " \n", + "-- forOf :: Traversal s t a b -> s -> (a -> f b) -> f t\n", + ":t forOf\n", + "\n", + "-- sequenceAOf :: Traversal s t (f a) a -> s -> f t\n", + ":t sequenceAOf\n", + "\n", + "sequenceAOf _1 (Just \"Garfield\", \"Lasagna\")\n", + "\n", + "sequenceAOf _1 (Nothing, \"Lasagna\")\n", + "\n", + "sequenceAOf (both . traversed) ([Just \"apples\"], [Just \"oranges\"])\n", + "\n", + "sequenceAOf (both . traversed) ([Just \"apples\"], [Nothing])" + ] + }, + { + "cell_type": "code", + "execution_count": null, + "metadata": {}, + "outputs": [], + "source": [ + "-- traverseOf :: Traversal s t a b -> (a -> f b) -> s -> f t\n", + "-- (%%~) :: Traversal s t a b -> (a -> f b) -> s -> f t\n", + "\n", + "((\"1\", \"2\") & both %%~ readMaybe) :: Maybe (Int, Int)\n", + "\n", + "((\"not a number\", \"2\") & both %%~ readMaybe) :: Maybe (Int, Int)" + ] + }, + { + "cell_type": "markdown", + "metadata": {}, + "source": [ + "### Exercises - Traversal Actions" + ] + }, + { + "cell_type": "code", + "execution_count": 98, + "metadata": {}, + "outputs": [ + { + "data": { + "text/plain": [ + "Nothing" + ] + }, + "metadata": {}, + "output_type": "display_data" + }, + { + "data": { + "text/plain": [ + "ZipList {getZipList = [[1,3],[2,4]]}" + ] + }, + "metadata": {}, + "output_type": "display_data" + }, + { + "data": { + "text/plain": [ + "ZipList {getZipList = [[('a',1),('b',3)],[('a',2),('b',4)]]}" + ] + }, + "metadata": {}, + "output_type": "display_data" + }, + { + "data": { + "text/plain": [ + "(([1,2,3],(4,5)),5)" + ] + }, + "metadata": {}, + "output_type": "display_data" + } + ], + "source": [ + "sequenceAOf _1 (Nothing, \"Rosebug\")\n", + "\n", + "-- sequenceAOf (traversed . _1) [(\"ab\", 1), (\"cd\", 2)]\n", + "\n", + "sequenceAOf traversed [ZipList [1, 2], ZipList [3, 4]]\n", + "\n", + "sequenceAOf (traversed . _2) [('a', ZipList [1, 2]), ('b', ZipList [3, 4])]\n", + "\n", + "import Control.Monad.State\n", + "let result = traverseOf (beside traversed both) (\\n -> modify (+n) >> get) ([1, 1, 1], (1, 1))\n", + "runState result 0" + ] + }, + { + "cell_type": "markdown", + "metadata": {}, + "source": [ + "### Custom Traversals" + ] + }, + { + "cell_type": "code", + "execution_count": 104, + "metadata": {}, + "outputs": [ + { + "data": { + "text/plain": [ + "[Deposit {_amount = 100},Withdrawal {_amount = 20},Withdrawal {_amount = 10}]" + ] + }, + "metadata": {}, + "output_type": "display_data" + }, + { + "data": { + "text/plain": [ + "[100,20,10]" + ] + }, + "metadata": {}, + "output_type": "display_data" + }, + { + "data": { + "text/plain": [ + "[10,30]" + ] + }, + "metadata": {}, + "output_type": "display_data" + }, + { + "data": { + "text/plain": [ + "[Deposit {_amount = 100},Withdrawal {_amount = 20},Deposit {_amount = 300}]" + ] + }, + "metadata": {}, + "output_type": "display_data" + } + ], + "source": [ + "-- values :: Traversal [a] [b] a b\n", + "\n", + "-- values :: Applicative f => (a -> f b) -> [a] -> f [b]\n", + "\n", + "values :: Applicative f => (a -> f b) -> [a] -> f [b]\n", + "values _ [] = pure []\n", + "values handler (a : as) = liftA2 (:) (handler a) (values handler as)\n", + "\n", + "data Transaction =\n", + " Withdrawal { _amount :: Int }\n", + " | Deposit { _amount :: Int }\n", + " deriving Show\n", + " \n", + "makeLenses ''Transaction\n", + "\n", + "newtype BankAccount =\n", + " BankAccount\n", + " { _transactions :: [Transaction]\n", + " } deriving Show\n", + "makeLenses ''BankAccount\n", + "\n", + "let aliceAccount = BankAccount [Deposit 100, Withdrawal 20, Withdrawal 10]\n", + "\n", + "aliceAccount ^.. transactions . traversed\n", + "\n", + "aliceAccount ^.. transactions . traversed . amount\n", + "\n", + "-- deposits :: Traversal' [Transaction] Int\n", + "-- deposits :: Traversal [Transaction] [Transaction] Int Int\n", + "deposits :: Applicative f => (Int -> f Int) -> [Transaction] -> f [Transaction]\n", + "deposits _ [] = pure []\n", + "deposits handler (Withdrawal amt : rest) =\n", + " liftA2 (:) (pure (Withdrawal amt)) (deposits handler rest)\n", + "deposits handler (Deposit amt : rest) =\n", + " liftA2 (:) (Deposit <$> (handler amt)) (deposits handler rest)\n", + " \n", + "[Deposit 10, Withdrawal 20, Deposit 30] ^.. deposits\n", + "\n", + "[Deposit 10, Withdrawal 20, Deposit 30] & deposits *~ 10" + ] + }, + { + "cell_type": "markdown", + "metadata": {}, + "source": [ + "### Exercises - Custom Traversals" + ] + }, + { + "cell_type": "code", + "execution_count": 105, + "metadata": {}, + "outputs": [], + "source": [ + "amountT :: Traversal' Transaction Int\n", + "amountT handler (Deposit n) = Deposit <$> handler n\n", + "amountT handler (Withdrawal n) = Withdrawal <$> handler n\n", + "\n", + "myBoth :: Traversal (a, a) (b, b) a b\n", + "myBoth handler (a, a') = liftA2 (,) (handler a) (handler a')\n", + "\n", + "transactionDelta :: Traversal' Transaction Int\n", + "transactionDelta handler (Deposit n) = Deposit <$> handler n\n", + "transactionDelta handler (Withdrawal n) = Withdrawal . negate <$> handler (negate n)\n", + "\n", + "left :: Traversal (Either a b) (Either a' b) a a'\n", + "left f (Left a) = Left <$> f a\n", + "left _ (Right b) = pure (Right b)\n", + "\n", + "beside :: Traversal s t a b -> Traversal s' t' a b -> Traversal (s,s') (t,t') a b\n", + "beside left' right' handler (s, s') = liftA2 (,) (s & left' %%~ handler) (s' & right' %%~ handler)" + ] + }, + { + "cell_type": "code", + "execution_count": 113, + "metadata": {}, + "outputs": [ + { + "data": { + "text/html": [ + "partsOf :: forall (f :: * -> *) s t a. Functor f => Traversing (->) f s t a a -> LensLike f s t [a] [a]" + ], + "text/plain": [ + "partsOf :: forall (f :: * -> *) s t a. Functor f => Traversing (->) f s t a a -> LensLike f s t [a] [a]" + ] + }, + "metadata": {}, + "output_type": "display_data" + }, + { + "data": { + "text/plain": [ + "\"abc\"" + ] + }, + "metadata": {}, + "output_type": "display_data" + }, + { + "data": { + "text/plain": [ + "[1,2,3]" + ] + }, + "metadata": {}, + "output_type": "display_data" + }, + { + "data": { + "text/plain": [ + "[('c',1),('a',2),('t',3)]" + ] + }, + "metadata": {}, + "output_type": "display_data" + }, + { + "data": { + "text/plain": [ + "[('l',1),('e',2),('o',3)]" + ] + }, + "metadata": {}, + "output_type": "display_data" + }, + { + "data": { + "text/plain": [ + "[('x',1),('b',2),('c',3)]" + ] + }, + "metadata": {}, + "output_type": "display_data" + }, + { + "data": { + "text/plain": [ + "[('c',1),('b',2),('a',3)]" + ] + }, + "metadata": {}, + "output_type": "display_data" + }, + { + "data": { + "text/plain": [ + "[('f',1),('o',2),('o',3)]" + ] + }, + "metadata": {}, + "output_type": "display_data" + }, + { + "data": { + "text/plain": [ + "[('o',1),('f',2),('f',3)]" + ] + }, + "metadata": {}, + "output_type": "display_data" + }, + { + "data": { + "text/plain": [ + "(\"a a desk how is\",\" like r\",\"aven writing\")" + ] + }, + "metadata": {}, + "output_type": "display_data" + } + ], + "source": [ + "-- partsOf :: Traversal' s a -> Lens' s [a]\n", + ":t partsOf\n", + "\n", + "[('a', 1), ('b', 2), ('c', 3)] ^. partsOf (traversed . _1)\n", + "[('a', 1), ('b', 2), ('c', 3)] ^. partsOf (traversed . _2)\n", + "\n", + "[('a', 1), ('b', 2), ('c', 3)]\n", + " & partsOf (traversed . _1) .~ ['c', 'a', 't']\n", + " \n", + "-- Any 'extra' list elements are simply ignored\n", + "[('a', 1), ('b', 2), ('c', 3)]\n", + " & partsOf (traversed . _1) .~ ['l', 'e', 'o', 'p', 'a', 'r', 'd']\n", + " \n", + "-- Providing too few elements will keep the originals\n", + "[('a', 1), ('b', 2), ('c', 3)]\n", + " & partsOf (traversed . _1) .~ ['x']\n", + " \n", + "[('a', 1), ('b', 2), ('c', 3)]\n", + " & partsOf (traversed . _1) %~ reverse\n", + " \n", + "[('o', 1), ('o', 2), ('f', 3)]\n", + " & partsOf (traversed . _1) %~ L.sort\n", + " \n", + "[('o', 1), ('o', 2), ('f', 3)]\n", + " & partsOf (traversed . _1) %~ tail\n", + "\n", + "(\"how is a raven \", \"like a \", \"writing desk\")\n", + " & partsOf (each . traversed) %~ unwords . L.sort . words" + ] + } + ], + "metadata": { + "kernelspec": { + "display_name": "Haskell", + "language": "haskell", + "name": "haskell" + }, + "language_info": { + "codemirror_mode": "ihaskell", + "file_extension": ".hs", + "name": "haskell", + "pygments_lexer": "Haskell", + "version": "8.6.5" + } + }, + "nbformat": 4, + "nbformat_minor": 2 +}