diff options
-rw-r--r-- | provider/posts/beuteltier-2.lhs | 173 |
1 files changed, 173 insertions, 0 deletions
diff --git a/provider/posts/beuteltier-2.lhs b/provider/posts/beuteltier-2.lhs new file mode 100644 index 0000000..bca4c86 --- /dev/null +++ b/provider/posts/beuteltier-2.lhs | |||
@@ -0,0 +1,173 @@ | |||
1 | --- | ||
2 | title: "Type level" utilities for an overly complicated feedreader | ||
3 | published: 2015-08-05 | ||
4 | tags: Beuteltier | ||
5 | --- | ||
6 | |||
7 | By popular (n=1) demand we will, in this post, be taking a look at | ||
8 | `beuteltier/Beuteltier/Types/Util.hs` the, creatively named, module providing some "type | ||
9 | level" utilities. | ||
10 | |||
11 | What I mean when I say "type level" is: additional instances (placed here when they | ||
12 | contain major design decisions and are not "Ord" or "Eq"), utilities not connected to | ||
13 | beuteltier itself (like the different flavours of `alter` below) | ||
14 | |||
15 | In contrast to the first, this post is straightforward enough to be read linearly. | ||
16 | |||
17 | > {-# LANGUAGE TypeSynonymInstances, FlexibleInstances #-} | ||
18 | > | ||
19 | > module Beuteltier.Types.Util | ||
20 | > ( -- * Constructing structures | ||
21 | > construct | ||
22 | > , construct' | ||
23 | > , alter | ||
24 | > , alter' | ||
25 | > -- * Dealing with 'ObjectGen's (here be dragons) | ||
26 | > , generateObject | ||
27 | > , liftGen | ||
28 | > -- * Equivalence on 'Object's (for nubbing) | ||
29 | > , Equivalent(..) | ||
30 | > -- * Operations on 'SearchQuery's | ||
31 | > , runQuery | ||
32 | > -- , runExpr | ||
33 | > ) where | ||
34 | > | ||
35 | > import Beuteltier.Types | ||
36 | > import Beuteltier.Types.Lenses | ||
37 | |||
38 | We make use of lenses (as provided by [lens](http://hackage.haskell.org/package/lens)) | ||
39 | extensively. | ||
40 | We won´t dedicate a post to `beuteltier/Beuteltier/Types/Lenses.hs` because it consists | ||
41 | mostly of the canonical invocations of | ||
42 | [makeLenses](http://hackage.haskell.org/package/lens-4.12.3/docs/Control-Lens-TH.html#v:makeLenses). | ||
43 | |||
44 | > import Data.Default | ||
45 | > | ||
46 | > import Prelude hiding (sequence) | ||
47 | > import Data.Traversable (sequence) | ||
48 | > | ||
49 | > import Control.Lens | ||
50 | > | ||
51 | > import Control.Monad.State.Lazy hiding (sequence) -- Why is this exported? | ||
52 | > | ||
53 | > import Data.Map (Map) | ||
54 | > import qualified Data.Map as Map | ||
55 | > | ||
56 | > import Data.Hashable (Hashable(..), hashUsing) | ||
57 | > | ||
58 | > import Data.Monoid ((<>)) | ||
59 | > | ||
60 | > import Data.Function (on) | ||
61 | > import Data.Maybe (mapMaybe) | ||
62 | > | ||
63 | > import Data.BoolExpr | ||
64 | |||
65 | Quite often we find ourselves in the position that we want to alter some small parts of a | ||
66 | complicated structure. We would therefore like to write the following: | ||
67 | |||
68 | ~~~ {.haskell .numberLines} | ||
69 | updateFoo :: Monad m => Foo -> m Foo | ||
70 | updateFoo = alter $ do | ||
71 | bar <~ constructNewBarInM | ||
72 | buz .= makeConstantBuz | ||
73 | ~~~ | ||
74 | |||
75 | The definitions below allow us not only to do so, but also provide some convenience | ||
76 | functions for constructing entirely new values and performing both operations in a pure | ||
77 | context. | ||
78 | |||
79 | > alter :: Monad m => s -> StateT s m a -> m s | ||
80 | > -- ^ Alter a complex structure monodically | ||
81 | > alter = flip execStateT | ||
82 | > | ||
83 | > alter' :: s -> State s a -> s | ||
84 | > -- ^ Specialization of 'alter' to 'Identity' | ||
85 | > alter' s = runIdentity . alter s | ||
86 | > | ||
87 | > construct :: (Monad m, Default s) => StateT s m a -> m s | ||
88 | > -- ^ Compute a complex structure monadically | ||
89 | > construct = alter def | ||
90 | > | ||
91 | > construct' :: Default s => State s a -> s | ||
92 | > -- ^ Specialization of 'construct' to 'Identity' | ||
93 | > construct' = runIdentity . construct | ||
94 | |||
95 | Sometimes we just really want to translate an `ObjectGen` to an `Object`. | ||
96 | |||
97 | > generateObject :: Monad f => ObjectGen f -> f Object | ||
98 | > -- ^ Run an object generator. | ||
99 | > -- Use iff /all/ components of an object are needed /in RAM now/. | ||
100 | > generateObject gen = construct $ do | ||
101 | > content <- lift $ gen ^. oContent >>= sequence | ||
102 | > thunks <- lift $ gen ^. oThunks >>= sequence | ||
103 | > meta <- lift $ gen ^. oMeta | ||
104 | > oContent .= return (fmap return content) | ||
105 | > oThunks .= return (fmap return thunks) | ||
106 | > oMeta .= return meta | ||
107 | > | ||
108 | > liftGen :: Monad f => Object -> ObjectGen f | ||
109 | > -- ^ Lift an 'Object' to be an 'ObjectGen' in any 'Monad' by the power of 'return' | ||
110 | > liftGen obj = construct' $ do | ||
111 | > oContent .= return (Map.map return $ obj ^. oContent') | ||
112 | > oThunks .= return (map return $ obj ^. oThunks') | ||
113 | > oMeta .= return (obj ^. oMeta') | ||
114 | |||
115 | We 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 | ||
117 | inserting. Thus we provide a definition of what we mean, when we say `Equivalent`. | ||
118 | |||
119 | > class Equivalent a where | ||
120 | > (~~) :: a -> a -> Bool | ||
121 | > | ||
122 | > -- | Two 'Object's are equivalent iff their content is identical as follows: | ||
123 | > -- the set of 'SubObjectName's both promised and actually occurring is identical | ||
124 | > -- and all 'SubObject's that actually occurr and share a 'SubObjectName' are | ||
125 | > -- identical (as per '(==)') | ||
126 | > -- | ||
127 | > -- Additionally we expect their 'Metadata' to be identical (as per '(==)') | ||
128 | > instance Equivalent Object where | ||
129 | > a ~~ b = (contentCompare `on` content) a b && ((==) `on` (^. oMeta')) a b | ||
130 | > where | ||
131 | > contentCompare :: (Ord k, Eq v) => Map k (Maybe v) -> Map k (Maybe v) -> Bool | ||
132 | > contentCompare a b = Map.foldl (&&) True $ Map.mergeWithKey combine setFalse setFalse a b | ||
133 | > combine _ a b = Just $ cmpMaybes a b | ||
134 | > setFalse = Map.map $ const False | ||
135 | > | ||
136 | > cmpMaybes Nothing _ = True | ||
137 | > cmpMaybes _ Nothing = True | ||
138 | > cmpMaybes (Just a) (Just b) = a == b | ||
139 | |||
140 | To speed up nubbing we also provide a quick way to "cache results". To make caching | ||
141 | meaningful we of course expect the following to hold: | ||
142 | |||
143 | ~~~ | ||
144 | a ~~ b ⇒ (hash a) == (hash b) | ||
145 | ~~~ | ||
146 | |||
147 | Note that we do not expect the converse to hold. We will thus require a second pass over | ||
148 | all objects sharing a hash to determine true equivalency. | ||
149 | |||
150 | > -- | Two 'Object's´ hashes are a first indication of whether they are 'Equivalent' | ||
151 | > instance Hashable Object where | ||
152 | > hashWithSalt = hashUsing $ \a -> (a ^. oMeta', Map.keys $ content a) | ||
153 | > | ||
154 | > content :: Object -> Map SubObjectName (Maybe SubObject) | ||
155 | > content obj = promised obj <> actual obj | ||
156 | > actual :: Object -> Map SubObjectName (Maybe SubObject) | ||
157 | > actual = fmap Just . (^. oContent') | ||
158 | > promised :: Object -> Map SubObjectName (Maybe SubObject) | ||
159 | > promised = Map.fromList . map (\n -> (n, Nothing)) . concat . promises | ||
160 | > promises :: Object -> [[SubObjectName]] | ||
161 | > promises = mapMaybe (^. tPromises) . (^. oThunks') | ||
162 | |||
163 | Evaluating a `SearchQuery` against an `ObjectGen` is, due to the structure of elementary | ||
164 | `SearchQuery`s quite straightforward. | ||
165 | |||
166 | > runQuery :: Monad f => SearchQuery f -> ObjectGen f -> f Bool | ||
167 | > -- ^ Run a 'SearchQuery' against an 'ObjectGen' | ||
168 | > runQuery query obj = liftM reduceBoolExpr $ sequence $ fmap ($ obj) query | ||
169 | > | ||
170 | > -- runExpr :: Monad f => ObjectGen f -> Predicate f -> f Bool | ||
171 | > -- -- ^ Run a 'Predicate' (»an atomic 'SearchQuery'«) against an 'ObjectGen' | ||
172 | > -- runExpr obj (Prim f) = f obj | ||
173 | > -- runExpr obj (Meta f) = liftM f (obj ^. oMeta) | ||