summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorGregor Kleen <gkleen@yggdrasil.li>2015-08-12 14:28:13 +0200
committerGregor Kleen <gkleen@yggdrasil.li>2015-08-12 14:28:13 +0200
commit0a8a750925e33b4bb68fe7bd508f8e3d94e758a9 (patch)
treedb5ea22ac0d338d166ee3000f97be49de6f0d632
parent9b2333f49cf510df8a42e0b2655ecb2c55c6d56c (diff)
parent07edcf47c71cc4552a406a4f7b7d9ae1d7fe8a23 (diff)
downloaddirty-haskell.org-0a8a750925e33b4bb68fe7bd508f8e3d94e758a9.tar
dirty-haskell.org-0a8a750925e33b4bb68fe7bd508f8e3d94e758a9.tar.gz
dirty-haskell.org-0a8a750925e33b4bb68fe7bd508f8e3d94e758a9.tar.bz2
dirty-haskell.org-0a8a750925e33b4bb68fe7bd508f8e3d94e758a9.tar.xz
dirty-haskell.org-0a8a750925e33b4bb68fe7bd508f8e3d94e758a9.zip
Merge branch 'master' of git.yggdrasil.li:dirty-haskell.org
-rw-r--r--provider/posts/beuteltier-2.lhs16
1 files changed, 11 insertions, 5 deletions
diff --git a/provider/posts/beuteltier-2.lhs b/provider/posts/beuteltier-2.lhs
index bca4c86..d5e0294 100644
--- a/provider/posts/beuteltier-2.lhs
+++ b/provider/posts/beuteltier-2.lhs
@@ -53,6 +53,9 @@ mostly of the canonical invocations of
53> import Data.Map (Map) 53> import Data.Map (Map)
54> import qualified Data.Map as Map 54> import qualified Data.Map as Map
55> 55>
56> import Data.Set (Set)
57> import qualified Data.Set as Set
58>
56> import Data.Hashable (Hashable(..), hashUsing) 59> import Data.Hashable (Hashable(..), hashUsing)
57> 60>
58> import Data.Monoid ((<>)) 61> import Data.Monoid ((<>))
@@ -66,10 +69,10 @@ Quite often we find ourselves in the position that we want to alter some small p
66complicated structure. We would therefore like to write the following: 69complicated structure. We would therefore like to write the following:
67 70
68~~~ {.haskell .numberLines} 71~~~ {.haskell .numberLines}
69updateFoo :: Monad m => Foo -> m Foo 72updateFoo :: Foo -> Monad Foo
70updateFoo = alter $ do 73updateFoo x = alter x $ do
71 bar <~ constructNewBarInM 74 bar <~ (constructNewBar :: Monad Bar)
72 buz .= makeConstantBuz 75 buz .= (makeConstantBuz :: Buz)
73~~~ 76~~~
74 77
75The definitions below allow us not only to do so, but also provide some convenience 78The definitions below allow us not only to do so, but also provide some convenience
@@ -113,7 +116,7 @@ Sometimes we just really want to translate an `ObjectGen` to an `Object`.
113> oMeta .= return (obj ^. oMeta') 116> oMeta .= return (obj ^. oMeta')
114 117
115We expect implementations of `insert` to perform what we call nubbing. That is removal of 118We expect implementations of `insert` to perform what we call nubbing. That is removal of
116'Object's that are, in some sense, `Equivalent` to the new one we´re currently 119`Object`s that are, in some sense, `Equivalent` to the new one we´re currently
117inserting. Thus we provide a definition of what we mean, when we say `Equivalent`. 120inserting. Thus we provide a definition of what we mean, when we say `Equivalent`.
118 121
119> class Equivalent a where 122> class Equivalent a where
@@ -150,6 +153,9 @@ all objects sharing a hash to determine true equivalency.
150> -- | Two 'Object's´ hashes are a first indication of whether they are 'Equivalent' 153> -- | Two 'Object's´ hashes are a first indication of whether they are 'Equivalent'
151> instance Hashable Object where 154> instance Hashable Object where
152> hashWithSalt = hashUsing $ \a -> (a ^. oMeta', Map.keys $ content a) 155> hashWithSalt = hashUsing $ \a -> (a ^. oMeta', Map.keys $ content a)
156>
157> instance Hashable MetaData where
158> hashWithSalt = hashUsing $ Set.toList . (^. mTags)
153> 159>
154> content :: Object -> Map SubObjectName (Maybe SubObject) 160> content :: Object -> Map SubObjectName (Maybe SubObject)
155> content obj = promised obj <> actual obj 161> content obj = promised obj <> actual obj