{ "cells": [ { "cell_type": "code", "execution_count": 2, "metadata": {}, "outputs": [ { "data": { "text/html": [ "view :: forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a" ], "text/plain": [ "view :: forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a" ] }, "metadata": {}, "output_type": "display_data" }, { "data": { "text/html": [ "set :: forall s t a b. ASetter s t a b -> b -> s -> t" ], "text/plain": [ "set :: forall s t a b. ASetter s t a b -> b -> s -> t" ] }, "metadata": {}, "output_type": "display_data" }, { "data": { "text/html": [ "over :: forall s t a b. ASetter s t a b -> (a -> b) -> s -> t" ], "text/plain": [ "over :: forall s t a b. ASetter s t a b -> (a -> b) -> s -> t" ] }, "metadata": {}, "output_type": "display_data" }, { "data": { "text/html": [ "(^.) :: forall s a. s -> Getting a s a -> a" ], "text/plain": [ "(^.) :: forall s a. s -> Getting a s a -> a" ] }, "metadata": {}, "output_type": "display_data" }, { "data": { "text/html": [ "(.~) :: forall s t a b. ASetter s t a b -> b -> s -> t" ], "text/plain": [ "(.~) :: forall s t a b. ASetter s t a b -> b -> s -> t" ] }, "metadata": {}, "output_type": "display_data" }, { "data": { "text/html": [ "(%~) :: forall s t a b. ASetter s t a b -> (a -> b) -> s -> t" ], "text/plain": [ "(%~) :: forall s t a b. ASetter s t a b -> (a -> b) -> s -> t" ] }, "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", "\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\n", "\n", ":t view\n", ":t set \n", ":t over\n", "\n", "-- Infix variants\n", "\n", ":t (^.) -- flip view\n", ":t (.~)\n", ":t (%~)" ] }, { "cell_type": "code", "execution_count": 4, "metadata": {}, "outputs": [ { "data": { "text/html": [ "(payload . cargo) :: forall (f :: * -> *). Functor f => (String -> f String) -> Ship -> f Ship" ], "text/plain": [ "(payload . cargo) :: forall (f :: * -> *). Functor f => (String -> f String) -> Ship -> f Ship" ] }, "metadata": {}, "output_type": "display_data" }, { "data": { "text/plain": [ "\"Livestock\"" ] }, "metadata": {}, "output_type": "display_data" }, { "data": { "text/plain": [ "\"Livestock\"" ] }, "metadata": {}, "output_type": "display_data" } ], "source": [ "-- view ^.\n", "\n", "data Payload =\n", " Payload { _weightKilos :: Int\n", " , _cargo :: String \n", " } deriving (Show)\n", " \n", "data Ship =\n", " Ship { _payload :: Payload\n", " } deriving (Show)\n", " \n", "makeLenses ''Payload\n", "makeLenses ''Ship\n", "\n", "serenity :: Ship\n", "serenity = Ship (Payload 50000 \"Livestock\")\n", "\n", ":t (payload . cargo)\n", "\n", "view (payload . cargo) serenity\n", "\n", "serenity ^. payload . cargo" ] }, { "cell_type": "code", "execution_count": 5, "metadata": {}, "outputs": [ { "data": { "text/plain": [ "Ship {_payload = Payload {_weightKilos = 50000, _cargo = \"Medicine\"}}" ] }, "metadata": {}, "output_type": "display_data" }, { "data": { "text/plain": [ "Ship {_payload = Payload {_weightKilos = 50000, _cargo = \"Medicine\"}}" ] }, "metadata": {}, "output_type": "display_data" } ], "source": [ "-- set .~\n", "\n", "set (payload . cargo) \"Medicine\" serenity\n", "\n", "serenity & payload . cargo .~ \"Medicine\"" ] }, { "cell_type": "code", "execution_count": 7, "metadata": {}, "outputs": [ { "data": { "text/plain": [ "Ship {_payload = Payload {_weightKilos = 2310, _cargo = \"Chocolate\"}}" ] }, "metadata": {}, "output_type": "display_data" }, { "data": { "text/plain": [ "Ship {_payload = Payload {_weightKilos = 2310, _cargo = \"Chocolate\"}}" ] }, "metadata": {}, "output_type": "display_data" } ], "source": [ "serenity\n", " & payload . cargo .~ \"Chocolate\"\n", " & payload . weightKilos .~ 2310\n", " \n", "serenity\n", " & set (payload . cargo) \"Chocolate\"\n", " & set (payload . weightKilos) 2310" ] }, { "cell_type": "code", "execution_count": 8, "metadata": {}, "outputs": [ { "data": { "text/plain": [ "Ship {_payload = Payload {_weightKilos = 49000, _cargo = \"Chocolate\"}}" ] }, "metadata": {}, "output_type": "display_data" } ], "source": [ "-- over %~\n", "\n", "serenity\n", " & payload . weightKilos %~ subtract 1000\n", " & payload . cargo .~ \"Chocolate\"" ] }, { "cell_type": "code", "execution_count": 12, "metadata": {}, "outputs": [ { "data": { "text/plain": [ "(2,35)" ] }, "metadata": {}, "output_type": "display_data" }, { "data": { "text/plain": [ "(2,15.0)" ] }, "metadata": {}, "output_type": "display_data" }, { "data": { "text/plain": [ "(8,30)" ] }, "metadata": {}, "output_type": "display_data" }, { "data": { "text/plain": [ "(True,30)" ] }, "metadata": {}, "output_type": "display_data" }, { "data": { "text/plain": [ "(\"abracadabra\",30)" ] }, "metadata": {}, "output_type": "display_data" } ], "source": [ "-- ^ Usually denote that the actions view/gets something\n", "-- . Typically used to represent the absence of any other modifiers\n", "\n", "-- % Means \"modify\" using a location\n", "-- ~ Denotes that this action updates or sets something\n", "\n", "-- +~, -~, *~ Add, substract or multiply a value with focus\n", "\n", "(2, 30) & _2 +~ 5\n", "\n", "-- //∼ Divide the focus by a provided denominator\n", "\n", "(2, 30) & _2 //~ 2\n", "\n", "-- ^∼ , ^^∼ , **∼\n", "\n", "(2, 30) & _1 ^~ 3\n", "\n", "-- ||∼ , &&∼\n", "\n", "(False, 30) & _1 ||~ True\n", "\n", "-- <>∼ mappend a value onto the focus (from the right).\n", "\n", "(\"abra\", 30) & _1 <>~ \"cadabra\"" ] }, { "cell_type": "code", "execution_count": 15, "metadata": {}, "outputs": [ { "data": { "text/plain": [ "(35,Thermometer {_temperature = 35})" ] }, "metadata": {}, "output_type": "display_data" }, { "data": { "text/plain": [ "(20,Thermometer {_temperature = 35})" ] }, "metadata": {}, "output_type": "display_data" } ], "source": [ "newtype Thermometer =\n", " Thermometer { _temperature :: Int\n", " } deriving Show\n", "makeLenses ''Thermometer\n", "\n", "-- < Get the altered focus in addition to modifying it.\n", "\n", "Thermometer 20 & temperature <+~ 15\n", "\n", "-- << Get the OLD focus in addition to setting a new one.\n", "\n", "Thermometer 20 & temperature <<+~ 15" ] }, { "cell_type": "markdown", "metadata": {}, "source": [ "### Exercises" ] }, { "cell_type": "code", "execution_count": 16, "metadata": {}, "outputs": [], "source": [ "-- 1.\n", "data Gate =\n", " Gate { _open :: Bool\n", " , _oilTemp :: Float\n", " } deriving Show\n", "makeLenses ''Gate\n", "\n", "data Army =\n", " Army { _archers :: Int\n", " , _knights :: Int\n", " } deriving Show\n", "makeLenses ''Army\n", "\n", "data Kingdom = \n", " Kingdom { _name :: String\n", " , _army :: Army\n", " , _gate :: Gate\n", " } deriving Show\n", "makeLenses ''Kingdom\n", " \n", "duloc :: Kingdom\n", "duloc = \n", " Kingdom { _name = \"Duloc\"\n", " , _army = Army { _archers = 22\n", " , _knights = 44\n", " }\n", " , _gate = Gate { _open = True\n", " , _oilTemp = 10.0\n", " }\n", " }" ] } ], "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 }