Skip to content

Instantly share code, notes, and snippets.

Show Gist options
  • Star 0 You must be signed in to star a gist
  • Fork 0 You must be signed in to fork a gist
  • Save mstksg/50ab748e13a72731f1b25098d823138e to your computer and use it in GitHub Desktop.
Save mstksg/50ab748e13a72731f1b25098d823138e to your computer and use it in GitHub Desktop.
How to get the HasNames instances less manually?
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE DefaultSignatures #-}
{-# LANGUAGE DeriveDataTypeable #-}
import ClassyPrelude
import Control.Lens
import Data.Typeable
import Data.Data
newtype Name = Name Text deriving (Monoid, Semigroup, IsString, Show, Typeable)
newtype LongName = LongName Text deriving (IsString, Show)
data Foo1 = Foo1 Int Name Bool deriving (Show, Data)
data Foo2 = Foo2 ([Foo1], Char) deriving (Show, Data)
data Foo3 = Foo3 Name Foo2 LongName Int deriving (Show, Data)
-- HasNames a means that a has 'Name' values inside that can be traversed.
class HasNames a where
traverseNames :: Traversal' a Name
default traverseNames :: Data a => Traversal' a Name
traverseNames = template
instance HasNames Name where
traverseNames = id
-- The 'Name' is the part before the comma. There is exactly one 'Name', so 'traverseNames' here is actualy
-- a Lens'.
instance HasNames LongName where
traverseNames =
let getter (LongName x) = Name $ takeWhile (/= ',') x
setter (LongName x) (Name newFront) =
let front = takeWhile (/= ',') x
rest = drop (length front) x
back = drop (length front + 1) x
in if null rest
then LongName newFront
else LongName $ newFront <> "," <> back
in lens getter setter
instance HasNames Foo1
instance HasNames Foo2 where
traverseNames f (Foo2 x) = Foo2 <$> (_1 . each . traverseNames) f x
instance HasNames Foo3
traverseNames f (Foo3 w x y z) = Foo3 <$> f w <*> traverseNames f x <*> traverseNames f y <*> pure z
foo1 :: Foo1
foo1 = Foo1 1 "abc" True
foo2 :: Foo2
foo2 = Foo2 ([foo1, foo1], 'a')
foo3 :: Foo3
foo3 = Foo3 "def" foo2 "ghi,jkl" 123
foo3' :: Foo3
foo3' = foo3 & traverseNames %~ (\x -> x <> x)
main :: IO ()
main = print foo3'
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment