A JSON value. Source: https://www.json.org/json-en.html

Code Snippet

src/Byte/Parser.hs

1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
239
240
241
242
243
244
245
246
247
248
249
250
251
252
253
254
255
256
257
258
259
260
261
262
263
264
265
266
267
268
269
270
271
272
273
274
275
276
277
278
279
280
281
282
283
284
285
286
287
288
289
290
291
292
293
294
295
296
297
298
299
300
301
302
303
304
305
306
307
308
--------------------------------------------------------------------------------
--
-- Byte.Parser, (c) 2020 SPISE MISU ApS
--
--------------------------------------------------------------------------------

{-# LANGUAGE Safe #-}

--------------------------------------------------------------------------------

module Byte.Parser
  ( Byte, Bytes
  , Output
    ( output
    )
  , Parser
    ( parse
    )
  , empty, many, some, (<|>)
  , sepBy
  , peekP
  , failP, spanP
  , getP
  , byteP, bytesP, chunkP
  , run
  )
where

--------------------------------------------------------------------------------

import           Control.Applicative
  ( Alternative
  , empty
  , many
  , some
  , (<|>)
  )
import           Data.Bits
  ( Bits
  , shiftL
  , shiftR
  )
import           Data.Char
  ( chr
  )
import           Data.Word
  ( Word8
  )

--------------------------------------------------------------------------------

type Byte  = Word8
type Bytes = [Byte]

type Index = Word
type Error = String

--------------------------------------------------------------------------------

newtype Output a = O
  { output :: (Either (Index, Error) (Index, a, Bytes))
  }

newtype Parser a = P
  { parse :: Index -> Bytes -> Output a
  }

--------------------------------------------------------------------------------

instance Show a => Show (Output a) where
  show o =
    case ppp "show" o of
      Left  e -> e
      Right a -> show a

--------------------------------------------------------------------------------

instance Functor Output where
  fmap _ (O (Left        e))  = O $ Left          e
  fmap f (O (Right (i,a,bs))) = O $ Right $ (i, f a, bs)

instance Applicative Output where
  pure          a           = O $ Right (0,   a, [])
  O (Left       e)  <*>   _ = O $ Left        e
  O (Right (_,f,_)) <*> O r =
    case r of
      Left      e      -> O $ Left        e
      Right (i, a, bs) -> O $ Right (i, f a, bs)

instance Alternative Output where
  empty             = O $ Left (0, [])
  O (Left  _) <|> o = o
  o           <|> _ = o

--------------------------------------------------------------------------------

instance Functor Parser where
  fmap f (P p) = P $ \ n bs ->
    case p n bs of
      O (Left  (i, e))     -> O $ Left  (i,   e)
      O (Right (i, a, xs)) -> O $ Right (i, f a, xs)

instance Applicative Parser where
  pure a              = P $ \ n bs -> O $ Right (n, a, bs)
  (<*>) (P p1) (P p2) = P $ \ n bs ->
    case p1 n bs of
      O (Left  (i, e))         -> O $ Left (i,    e)
      O (Right (i, f, xs))     ->
        case p2 i xs of
          O (Left  (j, e))     -> O $ Left  (j,   e)
          O (Right (j, a, ys)) -> O $ Right (j, f a, ys)

instance Monad Parser where
  (>>=) (P p) f = P $ \ n bs ->
    case p n bs of
      O (Left  (i, e))     -> O $ Left (i, e)
      O (Right (i, a, xs)) -> parse (f a) i xs

instance Alternative Parser where
  empty               = P $ \ i __ -> O $ Left (i, [])
  (<|>) (P p1) (P p2) = P $ \ n bs -> p1 n bs <|> p2 n bs

--------------------------------------------------------------------------------

sepBy
  :: (Alternative f)
  => f a
  -> f b
  -> f [a]
sepBy p sep =
  aux <|> pure []
  where
    aux = (:) <$> p <*> (many $ sep *> p)

--------------------------------------------------------------------------------

peekP
  :: Int
  -> Parser Bytes
peekP n =
  P $ \ i bs -> O $ Right (i, take n bs, bs)

failP
  :: Error
  -> Parser a
failP msg =
  P $ \ i bs -> O $ Left (i, err i msg bs)

spanP
  :: (Byte -> Bool)
  -> Parser Bytes
spanP f =
  P $ \ i bs -> aux i bs
  where
    aux i bs =
      case span f bs of
        ([],__) -> O $ Left  (i, err i "spanP" bs)
        (as,rs) -> O $ Right (i, as, rs)

getP
  :: Parser Byte
getP =
  P $ \ i bs -> aux i bs
  where
    aux i [    ] = O $ Left  (i, err i "getP" [])
    aux i (x:rs) = O $ Right (i+1, x, rs)

byteP
  :: Byte
  -> Parser Byte
byteP b =
  P $ \ i bs -> aux i bs
  where
    aux i    [    ] = O $ Left (i, err i "getP" [])
    aux i bs@(x:rs) =
      if b == x
      then            O $ Right (i+1, x, rs)
      else            O $ Left  (i, err i "byteP" bs)

bytesP
  :: Bytes
  -> Parser Bytes
bytesP =
  sequenceA . map byteP

chunkP
  :: Integral a
  => a
  -> Parser Bytes
chunkP n =
  P $ \ i bs ->
    case take m bs of
      xs | length xs == m -> O $ Right (i+j, take m xs, drop m bs)
      ___________________ -> O $ Left  (i, err i "chunkP" bs)
  where
    j = fromIntegral n
    m = fromIntegral n

--------------------------------------------------------------------------------

run
  :: Parser a
  -> Bytes
  -> Either Error a
run p =
  ppp "run" . parse p 0

--------------------------------------------------------------------------------

-- HELPERS

ppp
  :: String
  -> Output a
  -> Either Error a
ppp _ (O (Left  (_,e)))    = Left  $ e
ppp _ (O (Right (_,a,[]))) = Right a
ppp m (O (Right (i,_,bs))) = Left  $ err i ("ppp > " ++ m) bs

(.<.)
  :: Bits a
  => a
  -> Int
  -> a
(.<.) x y = x `shiftL` y

(.>.)
  :: Bits a
  => a
  -> Int
  -> a
(.>.) x y = x `shiftR` y

n2b
  :: (Bits a, Integral a)
  => Int
  -> (a -> a)
  -> a
  -> [Byte]
n2b b f =
  aux []
  where
    aux [ ] 0 = [ fromIntegral $! f 0 ]
    aux acc 0 = acc
    aux acc n =
      aux (r : acc) c
      where
        c =                   n         .>. b
        r = fromIntegral $ f (n - c * 1 .<. b)

b2h
  :: Word8
  -> [Char]
b2h =
  pad True 2 '0' . map (chr . fromIntegral) .  n2b 4 {- 2^4 = 016 -} aux
  where
    aux n
      | n <= 0x09 = 48 + n
      | otherwise = 55 + n

pad :: Bool -> Int -> Char -> String -> String
pad d n c x =
  if l > n
  then x
  else
    if d
    then replicate (n-l) c ++ x
    else x ++ replicate (n-l) c
  where
    l = length x

cof
  :: Int
  ->  [a]
  -> [[a]]
cof _ [] = [            ]
cof n xs = y : (cof n ys)
  where
    (y,ys) = splitAt n xs

err
  :: Index
  -> String
  -> [Word8]
  -> String
err i f bs =
  "# Parser error"                                 ++ "\n" ++
  "* Function:.....: " ++ f                        ++ "\n" ++
  "* Index.........: " ++ pad True 16 '0' (show i) ++ "\n" ++
  "* Unparsed bytes: " ++ show m                   ++ "\n" ++ out bs
  where
    m = length bs
    out xs = -- mimic `hexl-mode` in `emacs`
      (++ "…") $
      foldl (\a (x,y) -> a ++ (rp y) ++ " " ++ x ++ "\n") [] . zip zs . cof 40 $
      foldl (\a  x    -> a ++     x  ++ " ")              []          . cof 04 $
      concat   $
      map  b2h $
      ys
      where
        rp = pad False 40 ' '
        ys = take 640          xs
        zs = cof  016 $ map ec ys
        ec =
          \ b ->
            if b < 032 || b == 127
            then '.'
            else chr $ fromIntegral b

src/Byte/Parser/JSON.hs

1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
--------------------------------------------------------------------------------
--
-- Byte.Parser.JSON, (c) 2020 SPISE MISU ApS
--
--------------------------------------------------------------------------------

{-# LANGUAGE Safe #-}

--------------------------------------------------------------------------------

module Byte.Parser.JSON
  ( jsonP
  , stringP, numberP, objectP, arrayP, boolP, nullP
  )
where

--------------------------------------------------------------------------------

import           Data.Char
  ( chr
  )

import           Byte.Parser
  ( Byte
  , Parser
  , byteP
  , bytesP
  , chunkP
  , failP
  , getP
  , many
  , peekP
  , sepBy
  , spanP
  , (<|>)
  )
import qualified Data.JSON   as JSON

--------------------------------------------------------------------------------

jsonP
  :: Parser JSON.Value
jsonP =
  stringP <|> numberP <|> objectP <|> arrayP <|> boolP <|> nullP

stringP
  :: Parser JSON.Value
stringP =
  JSON.String <$> charsP

numberP
  :: Parser JSON.Value
numberP =
  JSON.Number . toRational . s2d . map (chr . fromIntegral) <$> aux
  where
    aux = sci <|> dec <|> int
    sci =
      d <|> i
      where
        d = cmb <$> dec <*> (byteP cce <|> byteP lce) <*> num
        i = cmb <$> int <*> (byteP cce <|> byteP lce) <*> num
    dec =
      n <|> d
      where
        n = (:) <$>         byteP neg <*> d
        d = cmb <$> num <*> byteP dot <*> num
    int =
      n <|> num
      where
        n = (:) <$> byteP neg <*> num
    neg = 045
    dot = 046
    cce = 069
    lce = 101
    num = spanP (\b -> 47 < b && b < 58)
    s2d = read :: String -> Double
    cmb = \xs y zs -> xs ++ [y] ++ zs

objectP
  :: Parser JSON.Value
objectP =
  JSON.Object <$> aux
  where
    aux =
      oc *> ws *> ps `sepBy` (ws *> cs <* ws) <* ws <* cc
      where
        ps =
          (\k _ v -> (k,v))
          <$> charsP
          <*> (ws *> kv <* ws)
          <*> jsonP
        oc = byteP 123
        cc = byteP 125
        cs = byteP 044
        kv = byteP 058
        ws = many  whitespaceP

arrayP
  :: Parser JSON.Value
arrayP =
  JSON.Array <$> aux
  where
    aux =
      ob *> ws *> jsonP `sepBy` (ws *> cs <* ws) <* ws <* cb
      where
        ob = byteP 091
        cb = byteP 093
        cs = byteP 044
        ws = many  whitespaceP

boolP
  :: Parser JSON.Value
boolP =
  trueP <|> falseP

nullP
  :: Parser JSON.Value
nullP =
  aux <$> bytesP [110,117,108,108]
  where
    aux _ = JSON.Null

--------------------------------------------------------------------------------

-- HELPERS

trueP
  :: Parser JSON.Value
trueP =
  aux <$> bytesP [116,114,117,101]
  where
    aux _ = JSON.Boolean True

falseP
  :: Parser JSON.Value
falseP =
  aux <$> bytesP [102,97,108,115,101]
  where
    aux _ = JSON.Boolean False

whitespaceP
  :: Parser Byte
whitespaceP =
 ht <|> lf <|> cr <|> sb
 where
   ht = byteP 009
   lf = byteP 010
   cr = byteP 013
   sb = byteP 032

charsP
  :: Parser [Char]
charsP =
  map (chr . fromIntegral)
  <$> (byteP 034 *> aux <* byteP 034)
  where
    aux =
      peekP n >>= \ bs ->
      case bs of
        [   ] -> pure []
        -- Reverse slash: '\\'
        [092] -> esc
        (b:_) ->
          if   g b
          then pure []
          else f
        where
          n = 1
          f = (:) <$> getP <*> aux
          g =
            \ b ->
              -- All except
              b <  032 || -- Control Codes
              b == 127 || -- Delete: '\DEL'
              b == 034    -- Quotation Mark
    esc =
      peekP n >>= \ bs ->
      case bs of
        [092     ] -> failP "charsP > invalid single reverse slash"
        -- Escaped backspace: '\b'
        [092, 098] -> f
        -- Escaped horizontal tab: '\t'
        [092, 116] -> f
        -- Escaped line feed: '\n
        [092, 110] -> f
        -- Escaped form feed: '\f'
        [092, 102] -> f
        -- Escaped carriage return: '\r
        [092, 114] -> f
        -- Escaped double quotes: '\\':'"'
        [092, 034] -> f
        -- Escaped forward slash: '\\':'/'
        [092, 047] -> f
        -- Escaped reverse slash: '\\':'\\'
        [092, 092] -> f
        [092, 117] -> uni
        __________ -> failP "charsP > invalid reverse slash sequence"
      where
        n = 2
        f = (++) <$> chunkP n <*> aux
    uni =
      peekP n >>= \ bs ->
      case bs of
        -- Unicode: '\\':'u':'0':'0':'0':'0' - '\\':'u':'F':'F':'F':'F'
        092:117:xs | length xs == 4 && all f xs -> g
        _______________________________________ -> failP e
      where
        n = 6
        f =
          \ b ->
            (047 < b && b < 058) || -- [ 0 .. 9 ]
            (064 < b && b < 071) || -- ['A'..'F']
            (092 < b && b < 103)    -- ['a'..'f']
        g = (++) <$> chunkP n <*> aux
        e = "charsP > invalid hex unicode"

src/Data/JSON.hs

1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
--------------------------------------------------------------------------------
--
-- Data.JSON, (c) 2020 SPISE MISU ApS
--
--------------------------------------------------------------------------------

{-# LANGUAGE Safe #-}

--------------------------------------------------------------------------------

module Data.JSON
  ( Value
    ( String
    , Number
    , Object
    , Array
    , Boolean
    , Null
    )
  , DTO
    ( encode
    , decode
    )
  )
where

--------------------------------------------------------------------------------

type Error = String

--------------------------------------------------------------------------------

data Value
  = String  String
  | Number  Rational
  | Object  [(String, Value)]
  | Array   [Value]
  | Boolean Bool
  | Null
  deriving
    ( Read
    , Show
    )

--------------------------------------------------------------------------------

class DTO a where
  encode :: a     -> Value
  decode :: Value -> Either Error a

exe/JsonByteStream.hs

1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
--------------------------------------------------------------------------------
--
-- JsonByteStream, (c) 2020 SPISE MISU ApS
--
--------------------------------------------------------------------------------

{-# LANGUAGE Safe #-}

--------------------------------------------------------------------------------

module Main (main) where

--------------------------------------------------------------------------------

import qualified Data.ByteString.Lazy as LBS
import           Text.Show.Pretty
  ( ppShow
  )

import qualified Byte.Parser          as Parser
import qualified Byte.Parser.JSON     as JSON

--------------------------------------------------------------------------------

main :: IO ()
main =
  LBS.getContents >>= putStrLn . aux . eof . LBS.unpack
  where
    eof [   ]  = [      ]
    eof [010]  = [      ]
    eof (b:bs) = b:eof bs
    aux bs =
      case Parser.run JSON.jsonP bs of
        Right ast -> ppShow ast
        Left  err -> err

json-bytestream-parser.cabal

cabal-version:   2.2

--------------------------------------------------------------------------------
--
-- JSON ByteStream Parser, (c) 2020 SPISE MISU ApS
--
--------------------------------------------------------------------------------

build-type:      Simple

name:            json-bytestream-parser
version:         0.11.0.0

synopsis:        A parser combinator tool to parse JSON bytestreams.
description:     A parser combinator tool to parse JSON bytestreams.

homepage:        https://gitlab.com/johndoe/json-bytestream-parser

license:         AGPL-3.0-only
license-file:    LICENSE.md

author:          Don Juan de la Cierva
maintainer:      Don Juan de la Cierva

category:        JSON

                
--------------------------------------------------------------------------------
-- COMMON
--------------------------------------------------------------------------------

common both
  default-language:
      Haskell98
  ghc-options:
      --------------------------------------------------------------------------
      -- GHC 8.6.4 Users Guide
      -- 9. Using GHC > 9.2. Warnings and sanity-checking
      -- * Base: https://downloads.haskell.org/~ghc/8.6.4/docs/html/users_guide/
      -- * File: using-warnings.html
      -- Warnings that are not enabled by -Wall:
      --------------------------------------------------------------------------
      -Wall
      -Wincomplete-record-updates
      -- -Wmonomorphism-restriction
      -- -Wimplicit-prelude
      -- -Wmissing-local-signatures
      -Wmissing-exported-signatures
      -- -Wmissing-export-lists
      -- -Wmissing-import-lists
      -Wmissing-home-modules
      -Widentities
      -Wredundant-constraints
      -- Added since GHC 8.4
      -Wpartial-fields 
      -- -Wmissed-specialisations
      -- -Wall-missed-specialisations
      --------------------------------------------------------------------------
      -- Added to allow instance definition in other files, in order to keep the 
      -- Effect module SAFE so it can be imported by the Process
      --------------------------------------------------------------------------
      -Wno-orphans
      -- Makes any warning into a fatal error.
      -Werror
      --------------------------------------------------------------------------
      -- Deterministic builds (Uniques):
      -- * https://gitlab.haskell.org/ghc/ghc/wikis/deterministic-builds#progress
      -- * https://www.youtube.com/watch?v=FNzTk4P4fL4 (08 GHC Determinism ICFP)
      --------------------------------------------------------------------------
      -dinitial-unique=0
      -dunique-increment=1
      --------------------------------------------------------------------------
      -- GHC 8.6.4 Users Guide
      -- 19. Known bugs and infelicities >
      -- 19.1. Haskell standards vs. Glasgow Haskell: language non-compliance >
      -- 19.1.1.3. Expressions and patterns
      -- * Base: https://downloads.haskell.org/~ghc/8.6.4/docs/html/users_guide/
      -- * File: bugs.html
      --------------------------------------------------------------------------
      -fpedantic-bottoms
      -- To use when GHC uses to many ticks:
      -- -ddump-simpl-stats
      -- -fsimpl-tick-factor=100
      --------------------------------------------------------------------------
      
common libs
  ghc-options:
      --------------------------------------------------------------------------
      -- GHC 8.6.4 Users Guide
      -- 12.40. Safe Haskell > ... > 12.40.1.1. Strict type-safety (good style)
      -- * Enforce good style, similar to the function of -Wall.
      -- Only Trustworthy packages can be trusted
      -- * Base: https://downloads.haskell.org/~ghc/8.6.4/docs/html/users_guide/
      -- * File: safe_haskell.html
      --------------------------------------------------------------------------
      -XSafe
      -fpackage-trust
      -trust=base
      --------------------------------------------------------------------------
        
common bins
  ghc-options:
      --------------------------------------------------------------------------
      -- GHC 8.6.4 Users Guide
      -- 9.3. Optimisation (code improvement)
      -- * Base: https://downloads.haskell.org/~ghc/8.6.4/docs/html/users_guide/
      -- * File: using-optimisation.html
      --------------------------------------------------------------------------
      -O2
      -- -threaded
      -- -rtsopts
      -- -with-rtsopts=-N
      --------------------------------------------------------------------------
      -- The -N flag built-in can be modified on runtime based on the system
      -- hosting the binary for optimal performance:
      -- - https://hackage.haskell.org/package/base/docs/GHC-Conc.html
      --   * getNumProcessors
      -- - https://hackage.haskell.org/package/base/docs/Control-Concurrent.html
      --   * setNumCapabilities
      --------------------------------------------------------------------------
      --------------------------------------------------------------------------
      -- GHC 8.6.4 Users Guide
      -- 12.40. Safe Haskell > ... > 12.40.1.1. Strict type-safety (good style)
      -- * Enforce good style, similar to the function of -Wall.
      -- Only Trustworthy packages can be trusted
      -- * Base: https://downloads.haskell.org/~ghc/8.6.4/docs/html/users_guide/
      -- * File: safe_haskell.html
      --------------------------------------------------------------------------
      -XSafe
      -fpackage-trust
      -trust=base
      -trust=bytestring
      -trust=pretty-show
      --------------------------------------------------------------------------

      
--------------------------------------------------------------------------------
-- LIBRARY
--------------------------------------------------------------------------------

library 
  import:
      both
    , libs
  hs-source-dirs:
      src
  exposed-modules:
      Byte.Parser
      Byte.Parser.JSON
      Data.JSON
  build-depends:
      -- Prelude
      base >= 4 && < 5
                  

--------------------------------------------------------------------------------
-- EXECUTABLES
--------------------------------------------------------------------------------

executable json-bytestream-parser
  import:
      both
    , bins
  main-is:
      JsonByteStream.hs
  hs-source-dirs:
      exe
  build-depends:
      json-bytestream-parser
      -- Prelude
    , base >= 4 && < 5
      -- bytes
    , bytestring
      -- pretty printing
    , pretty-show

                
--------------------------------------------------------------------------------
-- REFERENCES
--------------------------------------------------------------------------------
-- HaskellStarter/haskell-starter.cabal:
-- https://github.com/joshcough/HaskellStarter/blob/master/haskell-starter.cabal
--------------------------------------------------------------------------------

stack.yaml

resolver: lts-14.27
packages:
  - .
nix:
  enable: true
  packages: []
  path: [
    "nixpkgs=https://github.com/NixOS/nixpkgs-channels/archive/d858110.tar.gz"
  ]
  
## Reference
# Stack:
# - https://www.stackage.org/lts-14.27
# NixOS:
# - https://github.com/NixOS/nixpkgs-channels/branches/active
# - https://github.com/NixOS/nixpkgs-channels/tree/nixos-19.09
# - https://github.com/NixOS/nixpkgs-channels/tree/d858110
# - https://github.com/NixOS/nixpkgs-channels/archive/d858110.tar.gz

build.bash

#!/usr/bin/env bash

clear

bld="$(pwd)/.stack-work/install/x86_64-linux-nix/"
tgt="$(pwd)/bin"

echo "### Ensure folders exist:"
mkdir -v -p $bld;
mkdir -v -p $tgt;
echo

echo "### Clearing binaries:"
find $bld -mindepth 1 -name "*" -delete -print
find $tgt -mindepth 1 -name "*" -delete -print
echo

echo "### Stack building:" 
#stack clean
#stack build --verbosity debug
#stack build --fast
stack build
echo

src="$(stack path --local-install-root)/bin"

echo "### Copying binaries to local $tgt:" 
cp -v $src/* $tgt/
echo

echo "### Repoducible hashes:"
cd $tgt
for f in *; do
    # skip all non-binaries
    [[ $f == *.* ]] && continue
    echo -e $(sha256sum $f | cut -d " " -f 1): $f
done;
echo

Code Output:

dat/error-message-mimic-emacs-hexl-mode.json

[1,2,3,4,5,6,7,8,9,42,"5","\"]
[T480:~/code/haskell/json]$ cat dat/error-message-mimic-emacs-hexl-mode.json \
> | ./bin/json-bytestream-parser 
# Parser error
* Function:.....: byteP
* Index.........: 0000000000000000
* Unparsed bytes: 30
5B31 2C32 2C33 2C34 2C35 2C36 2C37 2C38  [1,2,3,4,5,6,7,8
2C39 2C34 322C 2235 222C 225C 225D       ,9,42,"5","\"]
…
[T480:~/code/haskell/json]$ 

dat/json.org-example-00.json

{
  "glossary": {
    "title": "example glossary",
    "GlossDiv": {
      "title": "S",
      "GlossList": {
        "GlossEntry": {
          "ID": "SGML",
          "SortAs": "SGML",
          "GlossTerm": "Standard Generalized Markup Language",
          "Acronym": "SGML",
          "Abbrev": "ISO 8879:1986",
          "GlossDef": {
            "para": "A meta-markup language, used to create markup languages such as DocBook.",
            "GlossSeeAlso": [
              "GML",
              "XML"
            ]
          },
          "GlossSee": "markup"
        }
      }
    }
  }
}
[T480:~/code/haskell/json]$ cat dat/json.org-example-00.json \
> | ./bin/json-bytestream-parser 
Object
  [ ( "glossary"
    , Object
        [ ( "title" , String "example glossary" )
        , ( "GlossDiv"
          , Object
              [ ( "title" , String "S" )
              , ( "GlossList"
                , Object
                    [ ( "GlossEntry"
                      , Object
                          [ ( "ID" , String "SGML" )
                          , ( "SortAs" , String "SGML" )
                          , ( "GlossTerm" , String "Standard Generalized Markup Language" )
                          , ( "Acronym" , String "SGML" )
                          , ( "Abbrev" , String "ISO 8879:1986" )
                          , ( "GlossDef"
                            , Object
                                [ ( "para"
                                  , String
                                      "A meta-markup language, used to create markup languages such as DocBook."
                                  )
                                , ( "GlossSeeAlso" , Array [ String "GML" , String "XML" ] )
                                ]
                            )
                          , ( "GlossSee" , String "markup" )
                          ]
                      )
                    ]
                )
              ]
          )
        ]
    )
  ]
[T480:~/code/haskell/json]$ 

dat/json.org-example-01.json

{
  "menu": {
    "id": "file",
    "value": "File",
    "popup": {
      "menuitem": [
        {
          "value": "New",
          "onclick": "CreateNewDoc()"
        },
        {
          "value": "Open",
          "onclick": "OpenDoc()"
        },
        {
          "value": "Close",
          "onclick": "CloseDoc()"
        }
      ]
    }
  }
}
[T480:~/code/haskell/json]$ cat dat/json.org-example-01.json \
> | ./bin/json-bytestream-parser 
Object
  [ ( "menu"
    , Object
        [ ( "id" , String "file" )
        , ( "value" , String "File" )
        , ( "popup"
          , Object
              [ ( "menuitem"
                , Array
                    [ Object
                        [ ( "value" , String "New" )
                        , ( "onclick" , String "CreateNewDoc()" )
                        ]
                    , Object
                        [ ( "value" , String "Open" )
                        , ( "onclick" , String "OpenDoc()" )
                        ]
                    , Object
                        [ ( "value" , String "Close" )
                        , ( "onclick" , String "CloseDoc()" )
                        ]
                    ]
                )
              ]
          )
        ]
    )
  ]
[T480:~/code/haskell/json]$ 

dat/json.org-example-02.json

{
  "widget": {
    "debug": "on",
    "window": {
      "title": "Sample Konfabulator Widget",
      "name": "main_window",
      "width": 500,
      "height": 500
    },
    "image": {
      "src": "Images/Sun.png",
      "name": "sun1",
      "hOffset": 250,
      "vOffset": 250,
      "alignment": "center"
    },
    "text": {
      "data": "Click Here",
      "size": 36,
      "style": "bold",
      "name": "text1",
      "hOffset": 250,
      "vOffset": 100,
      "alignment": "center",
      "onMouseUp": "sun1.opacity = (sun1.opacity / 100) * 90;"
    }
  }
}
[T480:~/code/haskell/json]$ cat dat/json.org-example-02.json \
> | ./bin/json-bytestream-parser 
Object
  [ ( "widget"
    , Object
        [ ( "debug" , String "on" )
        , ( "window"
          , Object
              [ ( "title" , String "Sample Konfabulator Widget" )
              , ( "name" , String "main_window" )
              , ( "width" , Number (500 % 1) )
              , ( "height" , Number (500 % 1) )
              ]
          )
        , ( "image"
          , Object
              [ ( "src" , String "Images/Sun.png" )
              , ( "name" , String "sun1" )
              , ( "hOffset" , Number (250 % 1) )
              , ( "vOffset" , Number (250 % 1) )
              , ( "alignment" , String "center" )
              ]
          )
        , ( "text"
          , Object
              [ ( "data" , String "Click Here" )
              , ( "size" , Number (36 % 1) )
              , ( "style" , String "bold" )
              , ( "name" , String "text1" )
              , ( "hOffset" , Number (250 % 1) )
              , ( "vOffset" , Number (100 % 1) )
              , ( "alignment" , String "center" )
              , ( "onMouseUp"
                , String "sun1.opacity = (sun1.opacity / 100) * 90;"
                )
              ]
          )
        ]
    )
  ]
[T480:~/code/haskell/json]$ 

dat/json.org-example-03.json

{
  "web-app": {
    "servlet": [
      {
        "servlet-name": "cofaxCDS",
        "servlet-class": "org.cofax.cds.CDSServlet",
        "init-param": {
          "configGlossary:installationAt": "Philadelphia, PA",
          "configGlossary:adminEmail": "ksm@pobox.com",
          "configGlossary:poweredBy": "Cofax",
          "configGlossary:poweredByIcon": "/images/cofax.gif",
          "configGlossary:staticPath": "/content/static",
          "templateProcessorClass": "org.cofax.WysiwygTemplate",
          "templateLoaderClass": "org.cofax.FilesTemplateLoader",
          "templatePath": "templates",
          "templateOverridePath": "",
          "defaultListTemplate": "listTemplate.htm",
          "defaultFileTemplate": "articleTemplate.htm",
          "useJSP": false,
          "jspListTemplate": "listTemplate.jsp",
          "jspFileTemplate": "articleTemplate.jsp",
          "cachePackageTagsTrack": 200,
          "cachePackageTagsStore": 200,
          "cachePackageTagsRefresh": 60,
          "cacheTemplatesTrack": 100,
          "cacheTemplatesStore": 50,
          "cacheTemplatesRefresh": 15,
          "cachePagesTrack": 200,
          "cachePagesStore": 100,
          "cachePagesRefresh": 10,
          "cachePagesDirtyRead": 10,
          "searchEngineListTemplate": "forSearchEnginesList.htm",
          "searchEngineFileTemplate": "forSearchEngines.htm",
          "searchEngineRobotsDb": "WEB-INF/robots.db",
          "useDataStore": true,
          "dataStoreClass": "org.cofax.SqlDataStore",
          "redirectionClass": "org.cofax.SqlRedirection",
          "dataStoreName": "cofax",
          "dataStoreDriver": "com.microsoft.jdbc.sqlserver.SQLServerDriver",
          "dataStoreUrl": "jdbc:microsoft:sqlserver://LOCALHOST:1433;DatabaseName=goon",
          "dataStoreUser": "sa",
          "dataStorePassword": "dataStoreTestQuery",
          "dataStoreTestQuery": "SET NOCOUNT ON;select test='test';",
          "dataStoreLogFile": "/usr/local/tomcat/logs/datastore.log",
          "dataStoreInitConns": 10,
          "dataStoreMaxConns": 100,
          "dataStoreConnUsageLimit": 100,
          "dataStoreLogLevel": "debug",
          "maxUrlLength": 500
        }
      },
      {
        "servlet-name": "cofaxEmail",
        "servlet-class": "org.cofax.cds.EmailServlet",
        "init-param": {
          "mailHost": "mail1",
          "mailHostOverride": "mail2"
        }
      },
      {
        "servlet-name": "cofaxAdmin",
        "servlet-class": "org.cofax.cds.AdminServlet"
      },
      {
        "servlet-name": "fileServlet",
        "servlet-class": "org.cofax.cds.FileServlet"
      },
      {
        "servlet-name": "cofaxTools",
        "servlet-class": "org.cofax.cms.CofaxToolsServlet",
        "init-param": {
          "templatePath": "toolstemplates/",
          "log": 1,
          "logLocation": "/usr/local/tomcat/logs/CofaxTools.log",
          "logMaxSize": "",
          "dataLog": 1,
          "dataLogLocation": "/usr/local/tomcat/logs/dataLog.log",
          "dataLogMaxSize": "",
          "removePageCache": "/content/admin/remove?cache=pages&id=",
          "removeTemplateCache": "/content/admin/remove?cache=templates&id=",
          "fileTransferFolder": "/usr/local/tomcat/webapps/content/fileTransferFolder",
          "lookInContext": 1,
          "adminGroupID": 4,
          "betaServer": true
        }
      }
    ],
    "servlet-mapping": {
      "cofaxCDS": "/",
      "cofaxEmail": "/cofaxutil/aemail/*",
      "cofaxAdmin": "/admin/*",
      "fileServlet": "/static/*",
      "cofaxTools": "/tools/*"
    },
    "taglib": {
      "taglib-uri": "cofax.tld",
      "taglib-location": "/WEB-INF/tlds/cofax.tld"
    }
  }
}
[T480:~/code/haskell/json]$ cat dat/json.org-example-03.json \
> | ./bin/json-bytestream-parser 
Object
  [ ( "web-app"
    , Object
        [ ( "servlet"
          , Array
              [ Object
                  [ ( "servlet-name" , String "cofaxCDS" )
                  , ( "servlet-class" , String "org.cofax.cds.CDSServlet" )
                  , ( "init-param"
                    , Object
                        [ ( "configGlossary:installationAt" , String "Philadelphia, PA" )
                        , ( "configGlossary:adminEmail" , String "ksm@pobox.com" )
                        , ( "configGlossary:poweredBy" , String "Cofax" )
                        , ( "configGlossary:poweredByIcon" , String "/images/cofax.gif" )
                        , ( "configGlossary:staticPath" , String "/content/static" )
                        , ( "templateProcessorClass" , String "org.cofax.WysiwygTemplate" )
                        , ( "templateLoaderClass"
                          , String "org.cofax.FilesTemplateLoader"
                          )
                        , ( "templatePath" , String "templates" )
                        , ( "templateOverridePath" , String "" )
                        , ( "defaultListTemplate" , String "listTemplate.htm" )
                        , ( "defaultFileTemplate" , String "articleTemplate.htm" )
                        , ( "useJSP" , Boolean False )
                        , ( "jspListTemplate" , String "listTemplate.jsp" )
                        , ( "jspFileTemplate" , String "articleTemplate.jsp" )
                        , ( "cachePackageTagsTrack" , Number (200 % 1) )
                        , ( "cachePackageTagsStore" , Number (200 % 1) )
                        , ( "cachePackageTagsRefresh" , Number (60 % 1) )
                        , ( "cacheTemplatesTrack" , Number (100 % 1) )
                        , ( "cacheTemplatesStore" , Number (50 % 1) )
                        , ( "cacheTemplatesRefresh" , Number (15 % 1) )
                        , ( "cachePagesTrack" , Number (200 % 1) )
                        , ( "cachePagesStore" , Number (100 % 1) )
                        , ( "cachePagesRefresh" , Number (10 % 1) )
                        , ( "cachePagesDirtyRead" , Number (10 % 1) )
                        , ( "searchEngineListTemplate"
                          , String "forSearchEnginesList.htm"
                          )
                        , ( "searchEngineFileTemplate" , String "forSearchEngines.htm" )
                        , ( "searchEngineRobotsDb" , String "WEB-INF/robots.db" )
                        , ( "useDataStore" , Boolean True )
                        , ( "dataStoreClass" , String "org.cofax.SqlDataStore" )
                        , ( "redirectionClass" , String "org.cofax.SqlRedirection" )
                        , ( "dataStoreName" , String "cofax" )
                        , ( "dataStoreDriver"
                          , String "com.microsoft.jdbc.sqlserver.SQLServerDriver"
                          )
                        , ( "dataStoreUrl"
                          , String
                              "jdbc:microsoft:sqlserver://LOCALHOST:1433;DatabaseName=goon"
                          )
                        , ( "dataStoreUser" , String "sa" )
                        , ( "dataStorePassword" , String "dataStoreTestQuery" )
                        , ( "dataStoreTestQuery"
                          , String "SET NOCOUNT ON;select test='test';"
                          )
                        , ( "dataStoreLogFile"
                          , String "/usr/local/tomcat/logs/datastore.log"
                          )
                        , ( "dataStoreInitConns" , Number (10 % 1) )
                        , ( "dataStoreMaxConns" , Number (100 % 1) )
                        , ( "dataStoreConnUsageLimit" , Number (100 % 1) )
                        , ( "dataStoreLogLevel" , String "debug" )
                        , ( "maxUrlLength" , Number (500 % 1) )
                        ]
                    )
                  ]
              , Object
                  [ ( "servlet-name" , String "cofaxEmail" )
                  , ( "servlet-class" , String "org.cofax.cds.EmailServlet" )
                  , ( "init-param"
                    , Object
                        [ ( "mailHost" , String "mail1" )
                        , ( "mailHostOverride" , String "mail2" )
                        ]
                    )
                  ]
              , Object
                  [ ( "servlet-name" , String "cofaxAdmin" )
                  , ( "servlet-class" , String "org.cofax.cds.AdminServlet" )
                  ]
              , Object
                  [ ( "servlet-name" , String "fileServlet" )
                  , ( "servlet-class" , String "org.cofax.cds.FileServlet" )
                  ]
              , Object
                  [ ( "servlet-name" , String "cofaxTools" )
                  , ( "servlet-class" , String "org.cofax.cms.CofaxToolsServlet" )
                  , ( "init-param"
                    , Object
                        [ ( "templatePath" , String "toolstemplates/" )
                        , ( "log" , Number (1 % 1) )
                        , ( "logLocation"
                          , String "/usr/local/tomcat/logs/CofaxTools.log"
                          )
                        , ( "logMaxSize" , String "" )
                        , ( "dataLog" , Number (1 % 1) )
                        , ( "dataLogLocation"
                          , String "/usr/local/tomcat/logs/dataLog.log"
                          )
                        , ( "dataLogMaxSize" , String "" )
                        , ( "removePageCache"
                          , String "/content/admin/remove?cache=pages&id="
                          )
                        , ( "removeTemplateCache"
                          , String "/content/admin/remove?cache=templates&id="
                          )
                        , ( "fileTransferFolder"
                          , String "/usr/local/tomcat/webapps/content/fileTransferFolder"
                          )
                        , ( "lookInContext" , Number (1 % 1) )
                        , ( "adminGroupID" , Number (4 % 1) )
                        , ( "betaServer" , Boolean True )
                        ]
                    )
                  ]
              ]
          )
        , ( "servlet-mapping"
          , Object
              [ ( "cofaxCDS" , String "/" )
              , ( "cofaxEmail" , String "/cofaxutil/aemail/*" )
              , ( "cofaxAdmin" , String "/admin/*" )
              , ( "fileServlet" , String "/static/*" )
              , ( "cofaxTools" , String "/tools/*" )
              ]
          )
        , ( "taglib"
          , Object
              [ ( "taglib-uri" , String "cofax.tld" )
              , ( "taglib-location" , String "/WEB-INF/tlds/cofax.tld" )
              ]
          )
        ]
    )
  ]
[T480:~/code/haskell/json]$ 

dat/json.org-example-04.json

{
  "menu": {
    "header": "SVG Viewer",
    "items": [
      {
        "id": "Open"
      },
      {
        "id": "OpenNew",
        "label": "Open New"
      },
      null,
      {
        "id": "ZoomIn",
        "label": "Zoom In"
      },
      {
        "id": "ZoomOut",
        "label": "Zoom Out"
      },
      {
        "id": "OriginalView",
        "label": "Original View"
      },
      null,
      {
        "id": "Quality"
      },
      {
        "id": "Pause"
      },
      {
        "id": "Mute"
      },
      null,
      {
        "id": "Find",
        "label": "Find..."
      },
      {
        "id": "FindAgain",
        "label": "Find Again"
      },
      {
        "id": "Copy"
      },
      {
        "id": "CopyAgain",
        "label": "Copy Again"
      },
      {
        "id": "CopySVG",
        "label": "Copy SVG"
      },
      {
        "id": "ViewSVG",
        "label": "View SVG"
      },
      {
        "id": "ViewSource",
        "label": "View Source"
      },
      {
        "id": "SaveAs",
        "label": "Save As"
      },
      null,
      {
        "id": "Help"
      },
      {
        "id": "About",
        "label": "About Adobe CVG Viewer..."
      }
    ]
  }
}
[T480:~/code/haskell/json]$ cat dat/json.org-example-04.json \
> | ./bin/json-bytestream-parser 
Object
  [ ( "menu"
    , Object
        [ ( "header" , String "SVG Viewer" )
        , ( "items"
          , Array
              [ Object [ ( "id" , String "Open" ) ]
              , Object
                  [ ( "id" , String "OpenNew" ) , ( "label" , String "Open New" ) ]
              , Null
              , Object
                  [ ( "id" , String "ZoomIn" ) , ( "label" , String "Zoom In" ) ]
              , Object
                  [ ( "id" , String "ZoomOut" ) , ( "label" , String "Zoom Out" ) ]
              , Object
                  [ ( "id" , String "OriginalView" )
                  , ( "label" , String "Original View" )
                  ]
              , Null
              , Object [ ( "id" , String "Quality" ) ]
              , Object [ ( "id" , String "Pause" ) ]
              , Object [ ( "id" , String "Mute" ) ]
              , Null
              , Object
                  [ ( "id" , String "Find" ) , ( "label" , String "Find..." ) ]
              , Object
                  [ ( "id" , String "FindAgain" )
                  , ( "label" , String "Find Again" )
                  ]
              , Object [ ( "id" , String "Copy" ) ]
              , Object
                  [ ( "id" , String "CopyAgain" )
                  , ( "label" , String "Copy Again" )
                  ]
              , Object
                  [ ( "id" , String "CopySVG" ) , ( "label" , String "Copy SVG" ) ]
              , Object
                  [ ( "id" , String "ViewSVG" ) , ( "label" , String "View SVG" ) ]
              , Object
                  [ ( "id" , String "ViewSource" )
                  , ( "label" , String "View Source" )
                  ]
              , Object
                  [ ( "id" , String "SaveAs" ) , ( "label" , String "Save As" ) ]
              , Null
              , Object [ ( "id" , String "Help" ) ]
              , Object
                  [ ( "id" , String "About" )
                  , ( "label" , String "About Adobe CVG Viewer..." )
                  ]
              ]
          )
        ]
    )
  ]
[T480:~/code/haskell/json]$ 

dat/old.reddit.com-r-haskell-ppp.json

{
  "kind": "Listing",
  "data": {
    "modhash": "",
    "dist": 26,
    "children": [
      {
        "kind": "t3",
        "data": {
          "approved_at_utc": null,
          "subreddit": "haskell",
          "selftext": "This is your opportunity to ask any questions you feel don't deserve their own threads, no matter how small or simple they might be!",
          "author_fullname": "t2_6l4z3",
          "saved": false,
          "mod_reason_title": null,
          "gilded": 0,
          "clicked": false,
          "title": "Monthly Hask Anything (May 2020)",
          "link_flair_richtext": [],
          "subreddit_name_prefixed": "r/haskell",
          "hidden": false,
          "pwls": 6,
          "link_flair_css_class": null,
          "downs": 0,
          "hide_score": false,
          "name": "t3_gazovx",
          "quarantine": false,
          "link_flair_text_color": "dark",
          "upvote_ratio": 0.96,
          "author_flair_background_color": null,
          "subreddit_type": "public",
          "ups": 20,
          "total_awards_received": 0,
          "media_embed": {},
          "author_flair_template_id": null,
          "is_original_content": false,
          "user_reports": [],
          "secure_media": null,
          "is_reddit_media_domain": false,
          "is_meta": false,
          "category": null,
          "secure_media_embed": {},
          "link_flair_text": null,
          "can_mod_post": false,
          "score": 20,
          "approved_by": null,
          "author_premium": true,
          "thumbnail": "",
          "edited": false,
          "author_flair_css_class": null,
          "author_flair_richtext": [],
          "gildings": {},
          "content_categories": null,
          "is_self": true,
          "mod_note": null,
          "created": 1588295176,
          "link_flair_type": "text",
          "wls": 6,
          "removed_by_category": null,
          "banned_by": null,
          "author_flair_type": "text",
          "domain": "self.haskell",
          "allow_live_comments": false,
          "selftext_html": "&lt;!-- SC_OFF --&gt;&lt;div class=\"md\"&gt;&lt;p&gt;This is your opportunity to ask any questions you feel don&amp;#39;t deserve their own threads, no matter how small or simple they might be!&lt;/p&gt;\n&lt;/div&gt;&lt;!-- SC_ON --&gt;",
          "likes": null,
          "suggested_sort": "new",
          "banned_at_utc": null,
          "view_count": null,
          "archived": false,
          "no_follow": true,
          "is_crosspostable": false,
          "pinned": false,
          "over_18": false,
          "all_awardings": [],
          "awarders": [],
          "media_only": false,
          "can_gild": false,
          "spoiler": false,
          "locked": false,
          "author_flair_text": null,
          "treatment_tags": [],
          "visited": false,
          "removed_by": null,
          "num_reports": null,
          "distinguished": "moderator",
          "subreddit_id": "t5_2qh36",
          "mod_reason_by": null,
          "removal_reason": null,
          "link_flair_background_color": "",
          "id": "gazovx",
          "is_robot_indexable": true,
          "report_reasons": null,
          "author": "AutoModerator",
          "discussion_type": null,
          "num_comments": 228,
          "send_replies": false,
          "whitelist_status": "all_ads",
          "contest_mode": false,
          "mod_reports": [],
          "author_patreon_flair": false,
          "author_flair_text_color": null,
          "permalink": "/r/haskell/comments/gazovx/monthly_hask_anything_may_2020/",
          "parent_whitelist_status": "all_ads",
          "stickied": true,
          "url": "https://old.reddit.com/r/haskell/comments/gazovx/monthly_hask_anything_may_2020/",
          "subreddit_subscribers": 55194,
          "created_utc": 1588266376,
          "num_crossposts": 0,
          "media": null,
          "is_video": false
        }
      },
      {
        "kind": "t3",
        "data": {
          "approved_at_utc": null,
          "subreddit": "haskell",
          "selftext": "",
          "author_fullname": "t2_4iein",
          "saved": false,
          "mod_reason_title": null,
          "gilded": 0,
          "clicked": false,
          "title": "Haskell Error Message, and How to Improve Them",
          "link_flair_richtext": [],
          "subreddit_name_prefixed": "r/haskell",
          "hidden": false,
          "pwls": 6,
          "link_flair_css_class": null,
          "downs": 0,
          "hide_score": false,
          "name": "t3_gnblom",
          "quarantine": false,
          "link_flair_text_color": "dark",
          "upvote_ratio": 0.87,
          "author_flair_background_color": null,
          "subreddit_type": "public",
          "ups": 33,
          "total_awards_received": 0,
          "media_embed": {},
          "author_flair_template_id": null,
          "is_original_content": false,
          "user_reports": [],
          "secure_media": null,
          "is_reddit_media_domain": false,
          "is_meta": false,
          "category": null,
          "secure_media_embed": {},
          "link_flair_text": null,
          "can_mod_post": false,
          "score": 33,
          "approved_by": null,
          "author_premium": false,
          "thumbnail": "",
          "edited": false,
          "author_flair_css_class": null,
          "author_flair_richtext": [],
          "gildings": {},
          "content_categories": null,
          "is_self": false,
          "mod_note": null,
          "created": 1590011148,
          "link_flair_type": "text",
          "wls": 6,
          "removed_by_category": null,
          "banned_by": null,
          "author_flair_type": "text",
          "domain": "anthony.noided.media",
          "allow_live_comments": false,
          "selftext_html": null,
          "likes": null,
          "suggested_sort": null,
          "banned_at_utc": null,
          "view_count": null,
          "archived": false,
          "no_follow": false,
          "is_crosspostable": false,
          "pinned": false,
          "over_18": false,
          "all_awardings": [],
          "awarders": [],
          "media_only": false,
          "can_gild": false,
          "spoiler": false,
          "locked": false,
          "author_flair_text": null,
          "treatment_tags": [],
          "visited": false,
          "removed_by": null,
          "num_reports": null,
          "distinguished": null,
          "subreddit_id": "t5_2qh36",
          "mod_reason_by": null,
          "removal_reason": null,
          "link_flair_background_color": "",
          "id": "gnblom",
          "is_robot_indexable": true,
          "report_reasons": null,
          "author": "THeShinyHObbiest",
          "discussion_type": null,
          "num_comments": 32,
          "send_replies": true,
          "whitelist_status": "all_ads",
          "contest_mode": false,
          "mod_reports": [],
          "author_patreon_flair": false,
          "author_flair_text_color": null,
          "permalink": "/r/haskell/comments/gnblom/haskell_error_message_and_how_to_improve_them/",
          "parent_whitelist_status": "all_ads",
          "stickied": false,
          "url": "https://anthony.noided.media/blog/haskell/programming/2020/05/14/haskell-errors.html",
          "subreddit_subscribers": 55194,
          "created_utc": 1589982348,
          "num_crossposts": 0,
          "media": null,
          "is_video": false
        }
      },
      {
        "kind": "t3",
        "data": {
          "approved_at_utc": null,
          "subreddit": "haskell",
          "selftext": "Hello dear redditors,\n\nI'm happy to announce my book \"Functional Design and Architecture\".\n\nIt's 80% done (8 chapters of 10, 600k symbols), and I decided to start selling it via Leanpub because it's already the most comprehensive guide on building of real software in Haskell and in FP.\n\n[Functional Design and Architecture (book) on Leanpub](https://leanpub.com/functional-design-and-architecture)\n\nThe book is focussing on many different design patterns, design principles and approaches, but the central role in it plays the approach I call Hierarchical Free Monads. Although the draft of chapters is available online [here](https://graninas.com/functional-design-and-architecture-book/), I won't be uncovering the rest, at least for now. I spent more than 2 years of writing the book, developing the approaches, providing materials and creating showcase projects. And now I think it's not an exaggeration to say that my Hierarchical Free Monads is the most developed approach in Haskell today.\n\nThe book is based on 2 projects, so you can play with the concepts easily:\n\n* [Hydra](https://github.com/graninas/Hydra), a full-fledged framework for building web services, multithreaded and concurrent applications with SQL and KV DB support. Contains 3 engines: Final Tagless, Free Monad and Church Encoded Free Monad, as well as several demo applications to compare these 3 approaches.\n* [Andromeda](https://github.com/graninas/Andromeda), a SCADA software for spaceship control.\n\nI also have a Patreon program for the book:\n\n[Patreon: \"Functional Design and Architecture\"](https://www.patreon.com/functional_design_and_architecture)\n\nAll the money collected from this program will be used to hire professional editors, designers, reviewers. I'm very grateful to all my Patron supporters! The supporters have an access to some exclusive content. They will get a edited book as well.\n\nThe following project is of my design also.\n\n* [Node](https://github.com/graninas/Node), a real-world all-in-one framework which is tested in production. It allows to build network actors and blockchain protocols, console applications, work with KV database and cryptography. Sample but not simple blockchain applications are also provided there.\n\nYou can get familiar with my long read articles explaining the concepts in details:\n\n* [Hierarchical Free Monads: The Most Developed Approach In Haskell (article)](https://github.com/graninas/hierarchical-free-monads-the-most-developed-approach-in-haskell)\n* [Automatic White-Box Testing with Free Monads (article, showcase)](https://github.com/graninas/automatic-whitebox-testing-showcase)\n* [Building network actors with Node Framework](https://gist.github.com/graninas/9beb8df5d88dda5fa21c47ce9bcb0e16)\n\nYou might also want to get familiar with my [list of materials on Software Design in Haskell](https://github.com/graninas/software-design-in-haskell).\n\nI'm also giving talks on this topic. Consider the following talks:\n\n* [Hierarchical Free Monads and Software Design in Functional Programming (talk)](https://www.youtube.com/watch?v=3GKQ4ni2pS0)\n* [Automatic Whitebox Testing with Free Monads (talk)](https://www.youtube.com/watch?v=ciZL-adDpVQ)\n* [Final Tagless vs Free Monads (talk, Russian)](https://www.youtube.com/watch?v=u1GGqDQyGfc) | [slides (English)](https://drive.google.com/open?id=1VhS8ySgk2w5RoN_l_Ar_axcE4Dzf97zLw1uuzUJQbCo)\n\nAnd this list of my materials is not even complete. For the record, I used Free Monads for making my own STM library: in Haskell and in C++. The implementation was incredibly simple due to the power of Free Monads to abstract things. There are different projects:\n\n* [stm-free](https://github.com/graninas/stm-free), my Free Monad based STM library in Haskell;\n* [cpp\\_stm-free](https://github.com/graninas/cpp_stm_free), the port to C++. Even more, it has 2 independent engines: Free Monad based and Church Encoded Free Monad based.\n* [Software Transactional Memory in C++: pure functional approach (Tutorial)](https://gist.github.com/graninas/c7e0a603f3a22c7e85daa4599bf92525) \\- the article, in case you like strange functional programming in C++.\n* [Functional Approach To Software Transactional Memory in C++ (talk, Russian)](https://www.youtube.com/watch?v=VHZPcz8HwZs) | [slides](https://docs.google.com/presentation/d/1_znOLZDKruKRNLA58TDlnXYQjTg9sXNJHPOLHfDTjeU/edit?usp=sharing) (English)\n* [cpp\\_parsec\\_free](https://github.com/graninas/cpp_parsec_free): a PoC of monadic parsers in C++ based on the same idea of Free Monads.\n* [Monadic Parsers in C++ (talk, Russian)](https://www.youtube.com/watch?v=q39PHTJDaLE) | [slides](https://docs.google.com/presentation/d/1zlwKBX8-DYVWUYmzvmKm7ggDVBugEJzY6OFSWjeQOA4/edit?usp=sharing) (English)\n* [hinteractive](https://github.com/graninas/hinteractive), an eDSL-like engine for interactive fiction games like Zork. Free Monad based.\n\nYes, all these projects show that I investigated Free Monads from all possible sides. But even more, there are two open source frameworks I (with my coworkers) designed for our employer, and these projects are heavily used in production:\n\n* [PureScript Presto](https://github.com/juspay/purescript-presto) \\- a framework for building mobile apps using a handy eDSL.\n* [PureScript Presto.Backend](https://github.com/juspay/purescript-presto-backend) \\- a framework for web RESTful backends.\n\nStill not convinced? Follow me ([Twitter](https://twitter.com/graninas), [GitHub](https://github.com/graninas), [LinkedIn](https://www.linkedin.com/in/alexander-granin-46889236/), [Telegram](https://web.telegram.org/#/im?p=@graninas), [Facebook](https://www.facebook.com/alexandr.granin)), hire me, and keep your eyes on my activity. Even more materials are coming!\n\nYours truly,\n\nAlexander Granin",
          "author_fullname": "t2_geqys",
          "saved": false,
          "mod_reason_title": null,
          "gilded": 0,
          "clicked": false,
          "title": "Book \"Functional Design and Architecture\"",
          "link_flair_richtext": [],
          "subreddit_name_prefixed": "r/haskell",
          "hidden": false,
          "pwls": 6,
          "link_flair_css_class": null,
          "downs": 0,
          "hide_score": false,
          "name": "t3_gmxfqz",
          "quarantine": false,
          "link_flair_text_color": "dark",
          "upvote_ratio": 0.97,
          "author_flair_background_color": null,
          "subreddit_type": "public",
          "ups": 152,
          "total_awards_received": 1,
          "media_embed": {},
          "author_flair_template_id": null,
          "is_original_content": false,
          "user_reports": [],
          "secure_media": null,
          "is_reddit_media_domain": false,
          "is_meta": false,
          "category": null,
          "secure_media_embed": {},
          "link_flair_text": null,
          "can_mod_post": false,
          "score": 152,
          "approved_by": null,
          "author_premium": false,
          "thumbnail": "",
          "edited": 1589979013,
          "author_flair_css_class": null,
          "author_flair_richtext": [],
          "gildings": {},
          "content_categories": null,
          "is_self": true,
          "mod_note": null,
          "created": 1589951620,
          "link_flair_type": "text",
          "wls": 6,
          "removed_by_category": null,
          "banned_by": null,
          "author_flair_type": "text",
          "domain": "self.haskell",
          "allow_live_comments": false,
          "selftext_html": "&lt;!-- SC_OFF --&gt;&lt;div class=\"md\"&gt;&lt;p&gt;Hello dear redditors,&lt;/p&gt;\n\n&lt;p&gt;I&amp;#39;m happy to announce my book &amp;quot;Functional Design and Architecture&amp;quot;.&lt;/p&gt;\n\n&lt;p&gt;It&amp;#39;s 80% done (8 chapters of 10, 600k symbols), and I decided to start selling it via Leanpub because it&amp;#39;s already the most comprehensive guide on building of real software in Haskell and in FP.&lt;/p&gt;\n\n&lt;p&gt;&lt;a href=\"https://leanpub.com/functional-design-and-architecture\"&gt;Functional Design and Architecture (book) on Leanpub&lt;/a&gt;&lt;/p&gt;\n\n&lt;p&gt;The book is focussing on many different design patterns, design principles and approaches, but the central role in it plays the approach I call Hierarchical Free Monads. Although the draft of chapters is available online &lt;a href=\"https://graninas.com/functional-design-and-architecture-book/\"&gt;here&lt;/a&gt;, I won&amp;#39;t be uncovering the rest, at least for now. I spent more than 2 years of writing the book, developing the approaches, providing materials and creating showcase projects. And now I think it&amp;#39;s not an exaggeration to say that my Hierarchical Free Monads is the most developed approach in Haskell today.&lt;/p&gt;\n\n&lt;p&gt;The book is based on 2 projects, so you can play with the concepts easily:&lt;/p&gt;\n\n&lt;ul&gt;\n&lt;li&gt;&lt;a href=\"https://github.com/graninas/Hydra\"&gt;Hydra&lt;/a&gt;, a full-fledged framework for building web services, multithreaded and concurrent applications with SQL and KV DB support. Contains 3 engines: Final Tagless, Free Monad and Church Encoded Free Monad, as well as several demo applications to compare these 3 approaches.&lt;/li&gt;\n&lt;li&gt;&lt;a href=\"https://github.com/graninas/Andromeda\"&gt;Andromeda&lt;/a&gt;, a SCADA software for spaceship control.&lt;/li&gt;\n&lt;/ul&gt;\n\n&lt;p&gt;I also have a Patreon program for the book:&lt;/p&gt;\n\n&lt;p&gt;&lt;a href=\"https://www.patreon.com/functional_design_and_architecture\"&gt;Patreon: &amp;quot;Functional Design and Architecture&amp;quot;&lt;/a&gt;&lt;/p&gt;\n\n&lt;p&gt;All the money collected from this program will be used to hire professional editors, designers, reviewers. I&amp;#39;m very grateful to all my Patron supporters! The supporters have an access to some exclusive content. They will get a edited book as well.&lt;/p&gt;\n\n&lt;p&gt;The following project is of my design also.&lt;/p&gt;\n\n&lt;ul&gt;\n&lt;li&gt;&lt;a href=\"https://github.com/graninas/Node\"&gt;Node&lt;/a&gt;, a real-world all-in-one framework which is tested in production. It allows to build network actors and blockchain protocols, console applications, work with KV database and cryptography. Sample but not simple blockchain applications are also provided there.&lt;/li&gt;\n&lt;/ul&gt;\n\n&lt;p&gt;You can get familiar with my long read articles explaining the concepts in details:&lt;/p&gt;\n\n&lt;ul&gt;\n&lt;li&gt;&lt;a href=\"https://github.com/graninas/hierarchical-free-monads-the-most-developed-approach-in-haskell\"&gt;Hierarchical Free Monads: The Most Developed Approach In Haskell (article)&lt;/a&gt;&lt;/li&gt;\n&lt;li&gt;&lt;a href=\"https://github.com/graninas/automatic-whitebox-testing-showcase\"&gt;Automatic White-Box Testing with Free Monads (article, showcase)&lt;/a&gt;&lt;/li&gt;\n&lt;li&gt;&lt;a href=\"https://gist.github.com/graninas/9beb8df5d88dda5fa21c47ce9bcb0e16\"&gt;Building network actors with Node Framework&lt;/a&gt;&lt;/li&gt;\n&lt;/ul&gt;\n\n&lt;p&gt;You might also want to get familiar with my &lt;a href=\"https://github.com/graninas/software-design-in-haskell\"&gt;list of materials on Software Design in Haskell&lt;/a&gt;.&lt;/p&gt;\n\n&lt;p&gt;I&amp;#39;m also giving talks on this topic. Consider the following talks:&lt;/p&gt;\n\n&lt;ul&gt;\n&lt;li&gt;&lt;a href=\"https://www.youtube.com/watch?v=3GKQ4ni2pS0\"&gt;Hierarchical Free Monads and Software Design in Functional Programming (talk)&lt;/a&gt;&lt;/li&gt;\n&lt;li&gt;&lt;a href=\"https://www.youtube.com/watch?v=ciZL-adDpVQ\"&gt;Automatic Whitebox Testing with Free Monads (talk)&lt;/a&gt;&lt;/li&gt;\n&lt;li&gt;&lt;a href=\"https://www.youtube.com/watch?v=u1GGqDQyGfc\"&gt;Final Tagless vs Free Monads (talk, Russian)&lt;/a&gt; | &lt;a href=\"https://drive.google.com/open?id=1VhS8ySgk2w5RoN_l_Ar_axcE4Dzf97zLw1uuzUJQbCo\"&gt;slides (English)&lt;/a&gt;&lt;/li&gt;\n&lt;/ul&gt;\n\n&lt;p&gt;And this list of my materials is not even complete. For the record, I used Free Monads for making my own STM library: in Haskell and in C++. The implementation was incredibly simple due to the power of Free Monads to abstract things. There are different projects:&lt;/p&gt;\n\n&lt;ul&gt;\n&lt;li&gt;&lt;a href=\"https://github.com/graninas/stm-free\"&gt;stm-free&lt;/a&gt;, my Free Monad based STM library in Haskell;&lt;/li&gt;\n&lt;li&gt;&lt;a href=\"https://github.com/graninas/cpp_stm_free\"&gt;cpp_stm-free&lt;/a&gt;, the port to C++. Even more, it has 2 independent engines: Free Monad based and Church Encoded Free Monad based.&lt;/li&gt;\n&lt;li&gt;&lt;a href=\"https://gist.github.com/graninas/c7e0a603f3a22c7e85daa4599bf92525\"&gt;Software Transactional Memory in C++: pure functional approach (Tutorial)&lt;/a&gt; - the article, in case you like strange functional programming in C++.&lt;/li&gt;\n&lt;li&gt;&lt;a href=\"https://www.youtube.com/watch?v=VHZPcz8HwZs\"&gt;Functional Approach To Software Transactional Memory in C++ (talk, Russian)&lt;/a&gt; | &lt;a href=\"https://docs.google.com/presentation/d/1_znOLZDKruKRNLA58TDlnXYQjTg9sXNJHPOLHfDTjeU/edit?usp=sharing\"&gt;slides&lt;/a&gt; (English)&lt;/li&gt;\n&lt;li&gt;&lt;a href=\"https://github.com/graninas/cpp_parsec_free\"&gt;cpp_parsec_free&lt;/a&gt;: a PoC of monadic parsers in C++ based on the same idea of Free Monads.&lt;/li&gt;\n&lt;li&gt;&lt;a href=\"https://www.youtube.com/watch?v=q39PHTJDaLE\"&gt;Monadic Parsers in C++ (talk, Russian)&lt;/a&gt; | &lt;a href=\"https://docs.google.com/presentation/d/1zlwKBX8-DYVWUYmzvmKm7ggDVBugEJzY6OFSWjeQOA4/edit?usp=sharing\"&gt;slides&lt;/a&gt; (English)&lt;/li&gt;\n&lt;li&gt;&lt;a href=\"https://github.com/graninas/hinteractive\"&gt;hinteractive&lt;/a&gt;, an eDSL-like engine for interactive fiction games like Zork. Free Monad based.&lt;/li&gt;\n&lt;/ul&gt;\n\n&lt;p&gt;Yes, all these projects show that I investigated Free Monads from all possible sides. But even more, there are two open source frameworks I (with my coworkers) designed for our employer, and these projects are heavily used in production:&lt;/p&gt;\n\n&lt;ul&gt;\n&lt;li&gt;&lt;a href=\"https://github.com/juspay/purescript-presto\"&gt;PureScript Presto&lt;/a&gt; - a framework for building mobile apps using a handy eDSL.&lt;/li&gt;\n&lt;li&gt;&lt;a href=\"https://github.com/juspay/purescript-presto-backend\"&gt;PureScript Presto.Backend&lt;/a&gt; - a framework for web RESTful backends.&lt;/li&gt;\n&lt;/ul&gt;\n\n&lt;p&gt;Still not convinced? Follow me (&lt;a href=\"https://twitter.com/graninas\"&gt;Twitter&lt;/a&gt;, &lt;a href=\"https://github.com/graninas\"&gt;GitHub&lt;/a&gt;, &lt;a href=\"https://www.linkedin.com/in/alexander-granin-46889236/\"&gt;LinkedIn&lt;/a&gt;, &lt;a href=\"https://web.telegram.org/#/im?p=@graninas\"&gt;Telegram&lt;/a&gt;, &lt;a href=\"https://www.facebook.com/alexandr.granin\"&gt;Facebook&lt;/a&gt;), hire me, and keep your eyes on my activity. Even more materials are coming!&lt;/p&gt;\n\n&lt;p&gt;Yours truly,&lt;/p&gt;\n\n&lt;p&gt;Alexander Granin&lt;/p&gt;\n&lt;/div&gt;&lt;!-- SC_ON --&gt;",
          "likes": null,
          "suggested_sort": null,
          "banned_at_utc": null,
          "view_count": null,
          "archived": false,
          "no_follow": false,
          "is_crosspostable": false,
          "pinned": false,
          "over_18": false,
          "all_awardings": [
            {
              "giver_coin_reward": null,
              "subreddit_id": null,
              "is_new": false,
              "days_of_drip_extension": 0,
              "coin_price": 500,
              "id": "award_43c43a35-15c5-4f73-91ef-fe538426435a",
              "penny_donate": null,
              "coin_reward": 100,
              "icon_url": "https://i.redd.it/award_images/t5_22cerq/xe5mw55w5v541_BlessUp.png",
              "days_of_premium": 0,
              "icon_height": 2048,
              "resized_icons": [
                {
                  "url": "https://preview.redd.it/award_images/t5_22cerq/xe5mw55w5v541_BlessUp.png?width=16&amp;height=16&amp;auto=webp&amp;s=e84e08de4b1352e679d612c063584341f56bc2b5",
                  "width": 16,
                  "height": 16
                },
                {
                  "url": "https://preview.redd.it/award_images/t5_22cerq/xe5mw55w5v541_BlessUp.png?width=32&amp;height=32&amp;auto=webp&amp;s=d01d7a3286bb55c235e217736c78c66e2d7d0c18",
                  "width": 32,
                  "height": 32
                },
                {
                  "url": "https://preview.redd.it/award_images/t5_22cerq/xe5mw55w5v541_BlessUp.png?width=48&amp;height=48&amp;auto=webp&amp;s=6ae7d390be614e44f1ec06141d0ba51d65494bff",
                  "width": 48,
                  "height": 48
                },
                {
                  "url": "https://preview.redd.it/award_images/t5_22cerq/xe5mw55w5v541_BlessUp.png?width=64&amp;height=64&amp;auto=webp&amp;s=1c88befd3d95c2ea37b95a7132db98d8a8730ae1",
                  "width": 64,
                  "height": 64
                },
                {
                  "url": "https://preview.redd.it/award_images/t5_22cerq/xe5mw55w5v541_BlessUp.png?width=128&amp;height=128&amp;auto=webp&amp;s=f97d6987f6545f6cb659f1fce7c304278a92f762",
                  "width": 128,
                  "height": 128
                }
              ],
              "icon_width": 2048,
              "start_date": null,
              "is_enabled": true,
              "description": "Prayers up for the blessed. Gives %{coin_symbol}100 Coins to both the author and the community.",
              "end_date": null,
              "subreddit_coin_reward": 100,
              "count": 1,
              "name": "Bless Up (Pro)",
              "icon_format": null,
              "award_sub_type": "GLOBAL",
              "penny_price": null,
              "award_type": "global"
            }
          ],
          "awarders": [],
          "media_only": false,
          "can_gild": false,
          "spoiler": false,
          "locked": false,
          "author_flair_text": null,
          "treatment_tags": [],
          "visited": false,
          "removed_by": null,
          "num_reports": null,
          "distinguished": null,
          "subreddit_id": "t5_2qh36",
          "mod_reason_by": null,
          "removal_reason": null,
          "link_flair_background_color": "",
          "id": "gmxfqz",
          "is_robot_indexable": true,
          "report_reasons": null,
          "author": "graninas",
          "discussion_type": null,
          "num_comments": 26,
          "send_replies": true,
          "whitelist_status": "all_ads",
          "contest_mode": false,
          "mod_reports": [],
          "author_patreon_flair": false,
          "author_flair_text_color": null,
          "permalink": "/r/haskell/comments/gmxfqz/book_functional_design_and_architecture/",
          "parent_whitelist_status": "all_ads",
          "stickied": false,
          "url": "https://old.reddit.com/r/haskell/comments/gmxfqz/book_functional_design_and_architecture/",
          "subreddit_subscribers": 55194,
          "created_utc": 1589922820,
          "num_crossposts": 2,
          "media": null,
          "is_video": false
        }
      },
      {
        "kind": "t3",
        "data": {
          "approved_at_utc": null,
          "subreddit": "haskell",
          "selftext": "",
          "author_fullname": "t2_3qjdu",
          "saved": false,
          "mod_reason_title": null,
          "gilded": 0,
          "clicked": false,
          "title": "DerivingVia sums-of-products",
          "link_flair_richtext": [],
          "subreddit_name_prefixed": "r/haskell",
          "hidden": false,
          "pwls": 6,
          "link_flair_css_class": null,
          "downs": 0,
          "hide_score": false,
          "name": "t3_gn8c5r",
          "quarantine": false,
          "link_flair_text_color": "dark",
          "upvote_ratio": 0.95,
          "author_flair_background_color": null,
          "subreddit_type": "public",
          "ups": 15,
          "total_awards_received": 0,
          "media_embed": {},
          "author_flair_template_id": null,
          "is_original_content": false,
          "user_reports": [],
          "secure_media": null,
          "is_reddit_media_domain": false,
          "is_meta": false,
          "category": null,
          "secure_media_embed": {},
          "link_flair_text": null,
          "can_mod_post": false,
          "score": 15,
          "approved_by": null,
          "author_premium": false,
          "thumbnail": "",
          "edited": false,
          "author_flair_css_class": null,
          "author_flair_richtext": [],
          "gildings": {},
          "content_categories": null,
          "is_self": false,
          "mod_note": null,
          "created": 1589996118,
          "link_flair_type": "text",
          "wls": 6,
          "removed_by_category": null,
          "banned_by": null,
          "author_flair_type": "text",
          "domain": "iceland_jack.brick.do",
          "allow_live_comments": false,
          "selftext_html": null,
          "likes": null,
          "suggested_sort": null,
          "banned_at_utc": null,
          "view_count": null,
          "archived": false,
          "no_follow": false,
          "is_crosspostable": false,
          "pinned": false,
          "over_18": false,
          "all_awardings": [],
          "awarders": [],
          "media_only": false,
          "can_gild": false,
          "spoiler": false,
          "locked": false,
          "author_flair_text": null,
          "treatment_tags": [],
          "visited": false,
          "removed_by": null,
          "num_reports": null,
          "distinguished": null,
          "subreddit_id": "t5_2qh36",
          "mod_reason_by": null,
          "removal_reason": null,
          "link_flair_background_color": "",
          "id": "gn8c5r",
          "is_robot_indexable": true,
          "report_reasons": null,
          "author": "Iceland_jack",
          "discussion_type": null,
          "num_comments": 5,
          "send_replies": true,
          "whitelist_status": "all_ads",
          "contest_mode": false,
          "mod_reports": [],
          "author_patreon_flair": false,
          "author_flair_text_color": null,
          "permalink": "/r/haskell/comments/gn8c5r/derivingvia_sumsofproducts/",
          "parent_whitelist_status": "all_ads",
          "stickied": false,
          "url": "https://iceland_jack.brick.do/e28e745c-40b8-4b0b-8148-1f1ae0c32d43",
          "subreddit_subscribers": 55194,
          "created_utc": 1589967318,
          "num_crossposts": 0,
          "media": null,
          "is_video": false
        }
      },
      {
        "kind": "t3",
        "data": {
          "approved_at_utc": null,
          "subreddit": "haskell",
          "selftext": "",
          "author_fullname": "t2_jxviuup",
          "saved": false,
          "mod_reason_title": null,
          "gilded": 0,
          "clicked": false,
          "title": "Alejandro Serrano Mena on Why Functors and Applicatives Compose but Monads Don't",
          "link_flair_richtext": [],
          "subreddit_name_prefixed": "r/haskell",
          "hidden": false,
          "pwls": 6,
          "link_flair_css_class": null,
          "downs": 0,
          "hide_score": false,
          "name": "t3_gn2tqs",
          "quarantine": false,
          "link_flair_text_color": "dark",
          "upvote_ratio": 0.98,
          "author_flair_background_color": null,
          "subreddit_type": "public",
          "ups": 52,
          "total_awards_received": 0,
          "media_embed": {
            "content": "&lt;iframe width=\"600\" height=\"338\" src=\"https://www.youtube.com/embed/eZ9FpG8May8?feature=oembed&amp;enablejsapi=1\" frameborder=\"0\" allow=\"accelerometer; autoplay; encrypted-media; gyroscope; picture-in-picture\" allowfullscreen&gt;&lt;/iframe&gt;",
            "width": 600,
            "scrolling": false,
            "height": 338
          },
          "author_flair_template_id": null,
          "is_original_content": false,
          "user_reports": [],
          "secure_media": {
            "type": "youtube.com",
            "oembed": {
              "provider_url": "https://www.youtube.com/",
              "version": "1.0",
              "title": "Alejandro Serrano Mena on Why Functors and Applicatives Compose but Monads Don't",
              "type": "video",
              "thumbnail_width": 480,
              "height": 338,
              "width": 600,
              "html": "&lt;iframe width=\"600\" height=\"338\" src=\"https://www.youtube.com/embed/eZ9FpG8May8?feature=oembed&amp;enablejsapi=1\" frameborder=\"0\" allow=\"accelerometer; autoplay; encrypted-media; gyroscope; picture-in-picture\" allowfullscreen&gt;&lt;/iframe&gt;",
              "author_name": "Berlin Functional Programming Group",
              "provider_name": "YouTube",
              "thumbnail_url": "https://i.ytimg.com/vi/eZ9FpG8May8/hqdefault.jpg",
              "thumbnail_height": 360,
              "author_url": "https://www.youtube.com/channel/UCNp-DVb8cQRIOo32sZhWgNg"
            }
          },
          "is_reddit_media_domain": false,
          "is_meta": false,
          "category": null,
          "secure_media_embed": {
            "content": "&lt;iframe width=\"600\" height=\"338\" src=\"https://www.youtube.com/embed/eZ9FpG8May8?feature=oembed&amp;enablejsapi=1\" frameborder=\"0\" allow=\"accelerometer; autoplay; encrypted-media; gyroscope; picture-in-picture\" allowfullscreen&gt;&lt;/iframe&gt;",
            "width": 600,
            "scrolling": false,
            "media_domain_url": "https://www.redditmedia.com/mediaembed/gn2tqs",
            "height": 338
          },
          "link_flair_text": null,
          "can_mod_post": false,
          "score": 52,
          "approved_by": null,
          "author_premium": false,
          "thumbnail": "",
          "edited": false,
          "author_flair_css_class": null,
          "author_flair_richtext": [],
          "gildings": {},
          "content_categories": null,
          "is_self": false,
          "mod_note": null,
          "created": 1589970172,
          "link_flair_type": "text",
          "wls": 6,
          "removed_by_category": null,
          "banned_by": null,
          "author_flair_type": "text",
          "domain": "youtube.com",
          "allow_live_comments": false,
          "selftext_html": null,
          "likes": null,
          "suggested_sort": null,
          "banned_at_utc": null,
          "view_count": null,
          "archived": false,
          "no_follow": false,
          "is_crosspostable": false,
          "pinned": false,
          "over_18": false,
          "all_awardings": [],
          "awarders": [],
          "media_only": false,
          "can_gild": false,
          "spoiler": false,
          "locked": false,
          "author_flair_text": null,
          "treatment_tags": [],
          "visited": false,
          "removed_by": null,
          "num_reports": null,
          "distinguished": null,
          "subreddit_id": "t5_2qh36",
          "mod_reason_by": null,
          "removal_reason": null,
          "link_flair_background_color": "",
          "id": "gn2tqs",
          "is_robot_indexable": true,
          "report_reasons": null,
          "author": "iedoub",
          "discussion_type": null,
          "num_comments": 5,
          "send_replies": true,
          "whitelist_status": "all_ads",
          "contest_mode": false,
          "mod_reports": [],
          "author_patreon_flair": false,
          "author_flair_text_color": null,
          "permalink": "/r/haskell/comments/gn2tqs/alejandro_serrano_mena_on_why_functors_and/",
          "parent_whitelist_status": "all_ads",
          "stickied": false,
          "url": "https://www.youtube.com/watch?v=eZ9FpG8May8&amp;feature=youtu.be",
          "subreddit_subscribers": 55194,
          "created_utc": 1589941372,
          "num_crossposts": 0,
          "media": {
            "type": "youtube.com",
            "oembed": {
              "provider_url": "https://www.youtube.com/",
              "version": "1.0",
              "title": "Alejandro Serrano Mena on Why Functors and Applicatives Compose but Monads Don't",
              "type": "video",
              "thumbnail_width": 480,
              "height": 338,
              "width": 600,
              "html": "&lt;iframe width=\"600\" height=\"338\" src=\"https://www.youtube.com/embed/eZ9FpG8May8?feature=oembed&amp;enablejsapi=1\" frameborder=\"0\" allow=\"accelerometer; autoplay; encrypted-media; gyroscope; picture-in-picture\" allowfullscreen&gt;&lt;/iframe&gt;",
              "author_name": "Berlin Functional Programming Group",
              "provider_name": "YouTube",
              "thumbnail_url": "https://i.ytimg.com/vi/eZ9FpG8May8/hqdefault.jpg",
              "thumbnail_height": 360,
              "author_url": "https://www.youtube.com/channel/UCNp-DVb8cQRIOo32sZhWgNg"
            }
          },
          "is_video": false
        }
      },
      {
        "kind": "t3",
        "data": {
          "approved_at_utc": null,
          "subreddit": "haskell",
          "selftext": "Saw a thread asking what Haskell is good for. I'm wondering now if it would be more interesting to hear what Haskell isn't good for.\n\nBy \"bad for\" I mean practically speaking given the current availability of ecosystem: libraries, tools, compiler extensions, devs, etc, etc. And, of course, if Haskell isn't good for something theoretically then it won't be good for it practically, so that's interesting too",
          "author_fullname": "t2_f4gx2",
          "saved": false,
          "mod_reason_title": null,
          "gilded": 0,
          "clicked": false,
          "title": "What is Haskell bad for?",
          "link_flair_richtext": [],
          "subreddit_name_prefixed": "r/haskell",
          "hidden": false,
          "pwls": 6,
          "link_flair_css_class": null,
          "downs": 0,
          "hide_score": false,
          "name": "t3_gmxsp4",
          "quarantine": false,
          "link_flair_text_color": "dark",
          "upvote_ratio": 0.97,
          "author_flair_background_color": null,
          "subreddit_type": "public",
          "ups": 27,
          "total_awards_received": 0,
          "media_embed": {},
          "author_flair_template_id": null,
          "is_original_content": false,
          "user_reports": [],
          "secure_media": null,
          "is_reddit_media_domain": false,
          "is_meta": false,
          "category": null,
          "secure_media_embed": {},
          "link_flair_text": null,
          "can_mod_post": false,
          "score": 27,
          "approved_by": null,
          "author_premium": false,
          "thumbnail": "",
          "edited": false,
          "author_flair_css_class": null,
          "author_flair_richtext": [],
          "gildings": {},
          "content_categories": null,
          "is_self": true,
          "mod_note": null,
          "created": 1589952776,
          "link_flair_type": "text",
          "wls": 6,
          "removed_by_category": null,
          "banned_by": null,
          "author_flair_type": "text",
          "domain": "self.haskell",
          "allow_live_comments": false,
          "selftext_html": "&lt;!-- SC_OFF --&gt;&lt;div class=\"md\"&gt;&lt;p&gt;Saw a thread asking what Haskell is good for. I&amp;#39;m wondering now if it would be more interesting to hear what Haskell isn&amp;#39;t good for.&lt;/p&gt;\n\n&lt;p&gt;By &amp;quot;bad for&amp;quot; I mean practically speaking given the current availability of ecosystem: libraries, tools, compiler extensions, devs, etc, etc. And, of course, if Haskell isn&amp;#39;t good for something theoretically then it won&amp;#39;t be good for it practically, so that&amp;#39;s interesting too&lt;/p&gt;\n&lt;/div&gt;&lt;!-- SC_ON --&gt;",
          "likes": null,
          "suggested_sort": null,
          "banned_at_utc": null,
          "view_count": null,
          "archived": false,
          "no_follow": false,
          "is_crosspostable": false,
          "pinned": false,
          "over_18": false,
          "all_awardings": [],
          "awarders": [],
          "media_only": false,
          "can_gild": false,
          "spoiler": false,
          "locked": false,
          "author_flair_text": null,
          "treatment_tags": [],
          "visited": false,
          "removed_by": null,
          "num_reports": null,
          "distinguished": null,
          "subreddit_id": "t5_2qh36",
          "mod_reason_by": null,
          "removal_reason": null,
          "link_flair_background_color": "",
          "id": "gmxsp4",
          "is_robot_indexable": true,
          "report_reasons": null,
          "author": "Dekans",
          "discussion_type": null,
          "num_comments": 65,
          "send_replies": true,
          "whitelist_status": "all_ads",
          "contest_mode": false,
          "mod_reports": [],
          "author_patreon_flair": false,
          "author_flair_text_color": null,
          "permalink": "/r/haskell/comments/gmxsp4/what_is_haskell_bad_for/",
          "parent_whitelist_status": "all_ads",
          "stickied": false,
          "url": "https://old.reddit.com/r/haskell/comments/gmxsp4/what_is_haskell_bad_for/",
          "subreddit_subscribers": 55194,
          "created_utc": 1589923976,
          "num_crossposts": 0,
          "media": null,
          "is_video": false
        }
      },
      {
        "kind": "t3",
        "data": {
          "approved_at_utc": null,
          "subreddit": "haskell",
          "selftext": "",
          "author_fullname": "t2_jxviuup",
          "saved": false,
          "mod_reason_title": null,
          "gilded": 0,
          "clicked": false,
          "title": "Benjamin Pierce: Backtracking Generators for Random Testing",
          "link_flair_richtext": [],
          "subreddit_name_prefixed": "r/haskell",
          "hidden": false,
          "pwls": 6,
          "link_flair_css_class": null,
          "downs": 0,
          "hide_score": false,
          "name": "t3_gmlw3d",
          "quarantine": false,
          "link_flair_text_color": "dark",
          "upvote_ratio": 0.92,
          "author_flair_background_color": null,
          "subreddit_type": "public",
          "ups": 57,
          "total_awards_received": 0,
          "media_embed": {},
          "author_flair_template_id": null,
          "is_original_content": false,
          "user_reports": [],
          "secure_media": null,
          "is_reddit_media_domain": false,
          "is_meta": false,
          "category": null,
          "secure_media_embed": {},
          "link_flair_text": null,
          "can_mod_post": false,
          "score": 57,
          "approved_by": null,
          "author_premium": false,
          "thumbnail": "",
          "edited": false,
          "author_flair_css_class": null,
          "author_flair_richtext": [],
          "gildings": {},
          "content_categories": null,
          "is_self": false,
          "mod_note": null,
          "created": 1589912401,
          "link_flair_type": "text",
          "wls": 6,
          "removed_by_category": null,
          "banned_by": null,
          "author_flair_type": "text",
          "domain": "youtube.com",
          "allow_live_comments": false,
          "selftext_html": null,
          "likes": null,
          "suggested_sort": null,
          "banned_at_utc": null,
          "view_count": null,
          "archived": false,
          "no_follow": false,
          "is_crosspostable": false,
          "pinned": false,
          "over_18": false,
          "all_awardings": [],
          "awarders": [],
          "media_only": false,
          "can_gild": false,
          "spoiler": false,
          "locked": false,
          "author_flair_text": null,
          "treatment_tags": [],
          "visited": false,
          "removed_by": null,
          "num_reports": null,
          "distinguished": null,
          "subreddit_id": "t5_2qh36",
          "mod_reason_by": null,
          "removal_reason": null,
          "link_flair_background_color": "",
          "id": "gmlw3d",
          "is_robot_indexable": true,
          "report_reasons": null,
          "author": "iedoub",
          "discussion_type": null,
          "num_comments": 2,
          "send_replies": true,
          "whitelist_status": "all_ads",
          "contest_mode": false,
          "mod_reports": [],
          "author_patreon_flair": false,
          "author_flair_text_color": null,
          "permalink": "/r/haskell/comments/gmlw3d/benjamin_pierce_backtracking_generators_for/",
          "parent_whitelist_status": "all_ads",
          "stickied": false,
          "url": "https://www.youtube.com/watch?v=dfZ94N0hS4I&amp;feature=youtu.be",
          "subreddit_subscribers": 55194,
          "created_utc": 1589883601,
          "num_crossposts": 0,
          "media": null,
          "is_video": false
        }
      },
      {
        "kind": "t3",
        "data": {
          "approved_at_utc": null,
          "subreddit": "haskell",
          "selftext": "",
          "author_fullname": "t2_2zl2",
          "saved": false,
          "mod_reason_title": null,
          "gilded": 0,
          "clicked": false,
          "title": "Haskenthetical - another take on \"Haskell with a Lisp syntax\"",
          "link_flair_richtext": [],
          "subreddit_name_prefixed": "r/haskell",
          "hidden": false,
          "pwls": 6,
          "link_flair_css_class": null,
          "downs": 0,
          "hide_score": false,
          "name": "t3_gmybcf",
          "quarantine": false,
          "link_flair_text_color": "dark",
          "upvote_ratio": 1,
          "author_flair_background_color": null,
          "subreddit_type": "public",
          "ups": 5,
          "total_awards_received": 0,
          "media_embed": {},
          "author_flair_template_id": null,
          "is_original_content": false,
          "user_reports": [],
          "secure_media": null,
          "is_reddit_media_domain": false,
          "is_meta": false,
          "category": null,
          "secure_media_embed": {},
          "link_flair_text": null,
          "can_mod_post": false,
          "score": 5,
          "approved_by": null,
          "author_premium": false,
          "thumbnail": "",
          "edited": false,
          "author_flair_css_class": null,
          "author_flair_richtext": [],
          "gildings": {},
          "content_categories": null,
          "is_self": false,
          "mod_note": null,
          "created": 1589954453,
          "link_flair_type": "text",
          "wls": 6,
          "removed_by_category": null,
          "banned_by": null,
          "author_flair_type": "text",
          "domain": "reasonableapproximation.net",
          "allow_live_comments": false,
          "selftext_html": null,
          "likes": null,
          "suggested_sort": null,
          "banned_at_utc": null,
          "view_count": null,
          "archived": false,
          "no_follow": false,
          "is_crosspostable": false,
          "pinned": false,
          "over_18": false,
          "all_awardings": [],
          "awarders": [],
          "media_only": false,
          "can_gild": false,
          "spoiler": false,
          "locked": false,
          "author_flair_text": null,
          "treatment_tags": [],
          "visited": false,
          "removed_by": null,
          "num_reports": null,
          "distinguished": null,
          "subreddit_id": "t5_2qh36",
          "mod_reason_by": null,
          "removal_reason": null,
          "link_flair_background_color": "",
          "id": "gmybcf",
          "is_robot_indexable": true,
          "report_reasons": null,
          "author": "philh",
          "discussion_type": null,
          "num_comments": 2,
          "send_replies": true,
          "whitelist_status": "all_ads",
          "contest_mode": false,
          "mod_reports": [],
          "author_patreon_flair": false,
          "author_flair_text_color": null,
          "permalink": "/r/haskell/comments/gmybcf/haskenthetical_another_take_on_haskell_with_a/",
          "parent_whitelist_status": "all_ads",
          "stickied": false,
          "url": "http://reasonableapproximation.net/2020/05/19/haskenthetical.html",
          "subreddit_subscribers": 55194,
          "created_utc": 1589925653,
          "num_crossposts": 0,
          "media": null,
          "is_video": false
        }
      },
      {
        "kind": "t3",
        "data": {
          "approved_at_utc": null,
          "subreddit": "haskell",
          "selftext": "",
          "author_fullname": "t2_4hurx",
          "saved": false,
          "mod_reason_title": null,
          "gilded": 0,
          "clicked": false,
          "title": "How to define JSON instances quickly",
          "link_flair_richtext": [],
          "subreddit_name_prefixed": "r/haskell",
          "hidden": false,
          "pwls": 6,
          "link_flair_css_class": null,
          "downs": 0,
          "hide_score": false,
          "name": "t3_gmmp65",
          "quarantine": false,
          "link_flair_text_color": "dark",
          "upvote_ratio": 0.93,
          "author_flair_background_color": null,
          "subreddit_type": "public",
          "ups": 23,
          "total_awards_received": 0,
          "media_embed": {},
          "author_flair_template_id": null,
          "is_original_content": false,
          "user_reports": [],
          "secure_media": null,
          "is_reddit_media_domain": false,
          "is_meta": false,
          "category": null,
          "secure_media_embed": {},
          "link_flair_text": null,
          "can_mod_post": false,
          "score": 23,
          "approved_by": null,
          "author_premium": false,
          "thumbnail": "",
          "edited": false,
          "author_flair_css_class": null,
          "author_flair_richtext": [],
          "gildings": {},
          "content_categories": null,
          "is_self": false,
          "mod_note": null,
          "created": 1589916349,
          "link_flair_type": "text",
          "wls": 6,
          "removed_by_category": null,
          "banned_by": null,
          "author_flair_type": "text",
          "domain": "dev.to",
          "allow_live_comments": false,
          "selftext_html": null,
          "likes": null,
          "suggested_sort": null,
          "banned_at_utc": null,
          "view_count": null,
          "archived": false,
          "no_follow": false,
          "is_crosspostable": false,
          "pinned": false,
          "over_18": false,
          "all_awardings": [],
          "awarders": [],
          "media_only": false,
          "can_gild": false,
          "spoiler": false,
          "locked": false,
          "author_flair_text": null,
          "treatment_tags": [],
          "visited": false,
          "removed_by": null,
          "num_reports": null,
          "distinguished": null,
          "subreddit_id": "t5_2qh36",
          "mod_reason_by": null,
          "removal_reason": null,
          "link_flair_background_color": "",
          "id": "gmmp65",
          "is_robot_indexable": true,
          "report_reasons": null,
          "author": "taylorfausak",
          "discussion_type": null,
          "num_comments": 9,
          "send_replies": true,
          "whitelist_status": "all_ads",
          "contest_mode": false,
          "mod_reports": [],
          "author_patreon_flair": false,
          "author_flair_text_color": null,
          "permalink": "/r/haskell/comments/gmmp65/how_to_define_json_instances_quickly/",
          "parent_whitelist_status": "all_ads",
          "stickied": false,
          "url": "https://dev.to/tfausak/how-to-define-json-instances-quickly-5ei7",
          "subreddit_subscribers": 55194,
          "created_utc": 1589887549,
          "num_crossposts": 0,
          "media": null,
          "is_video": false
        }
      },
      {
        "kind": "t3",
        "data": {
          "approved_at_utc": null,
          "subreddit": "haskell",
          "selftext": "I try to manage my packages by nix, but the following command `nix-env -iA nixpkgs.stack` do not create a `.stack` folder for me, and then run stack global will throw exception like this.\n\n```shell\n$ stack ghci  \nopenAnonymousTempFileFromDir: inappropriate type (Is a directory)\n```",
          "author_fullname": "t2_22yozddx",
          "saved": false,
          "mod_reason_title": null,
          "gilded": 0,
          "clicked": false,
          "title": "Stack installed by nix seems do not create `.stack` folder under home dir properly.",
          "link_flair_richtext": [],
          "subreddit_name_prefixed": "r/haskell",
          "hidden": false,
          "pwls": 6,
          "link_flair_css_class": null,
          "downs": 0,
          "hide_score": false,
          "name": "t3_gn3vhr",
          "quarantine": false,
          "link_flair_text_color": "dark",
          "upvote_ratio": 0.5,
          "author_flair_background_color": null,
          "subreddit_type": "public",
          "ups": 0,
          "total_awards_received": 0,
          "media_embed": {},
          "author_flair_template_id": null,
          "is_original_content": false,
          "user_reports": [],
          "secure_media": null,
          "is_reddit_media_domain": false,
          "is_meta": false,
          "category": null,
          "secure_media_embed": {},
          "link_flair_text": null,
          "can_mod_post": false,
          "score": 0,
          "approved_by": null,
          "author_premium": false,
          "thumbnail": "",
          "edited": false,
          "author_flair_css_class": null,
          "author_flair_richtext": [],
          "gildings": {},
          "content_categories": null,
          "is_self": true,
          "mod_note": null,
          "created": 1589974381,
          "link_flair_type": "text",
          "wls": 6,
          "removed_by_category": null,
          "banned_by": null,
          "author_flair_type": "text",
          "domain": "self.haskell",
          "allow_live_comments": false,
          "selftext_html": "&lt;!-- SC_OFF --&gt;&lt;div class=\"md\"&gt;&lt;p&gt;I try to manage my packages by nix, but the following command &lt;code&gt;nix-env -iA nixpkgs.stack&lt;/code&gt; do not create a &lt;code&gt;.stack&lt;/code&gt; folder for me, and then run stack global will throw exception like this.&lt;/p&gt;\n\n&lt;p&gt;&lt;code&gt;shell\n$ stack ghci  \nopenAnonymousTempFileFromDir: inappropriate type (Is a directory)\n&lt;/code&gt;&lt;/p&gt;\n&lt;/div&gt;&lt;!-- SC_ON --&gt;",
          "likes": null,
          "suggested_sort": null,
          "banned_at_utc": null,
          "view_count": null,
          "archived": false,
          "no_follow": true,
          "is_crosspostable": false,
          "pinned": false,
          "over_18": false,
          "all_awardings": [],
          "awarders": [],
          "media_only": false,
          "can_gild": false,
          "spoiler": false,
          "locked": false,
          "author_flair_text": null,
          "treatment_tags": [],
          "visited": false,
          "removed_by": null,
          "num_reports": null,
          "distinguished": null,
          "subreddit_id": "t5_2qh36",
          "mod_reason_by": null,
          "removal_reason": null,
          "link_flair_background_color": "",
          "id": "gn3vhr",
          "is_robot_indexable": true,
          "report_reasons": null,
          "author": "wangqiao11",
          "discussion_type": null,
          "num_comments": 3,
          "send_replies": true,
          "whitelist_status": "all_ads",
          "contest_mode": false,
          "mod_reports": [],
          "author_patreon_flair": false,
          "author_flair_text_color": null,
          "permalink": "/r/haskell/comments/gn3vhr/stack_installed_by_nix_seems_do_not_create_stack/",
          "parent_whitelist_status": "all_ads",
          "stickied": false,
          "url": "https://old.reddit.com/r/haskell/comments/gn3vhr/stack_installed_by_nix_seems_do_not_create_stack/",
          "subreddit_subscribers": 55194,
          "created_utc": 1589945581,
          "num_crossposts": 0,
          "media": null,
          "is_video": false
        }
      },
      {
        "kind": "t3",
        "data": {
          "approved_at_utc": null,
          "subreddit": "haskell",
          "selftext": "I've been beating my head against this issue for a while and thought maybe someone here has a good idea of how to approach this problem.   \nI'm working on a program which has a simple terminal GUI interface using [brick](https://github.com/jtdaugherty/brick), and now I want to be able to run SMT queries in the program using the [SBV](https://hackage.haskell.org/package/sbv-8.6) library. The problem is that the interaction between the program and the SMT solver is being tracked in a monad context (\\`[MonadQuery](https://hackage.haskell.org/package/sbv-8.6/docs/src/Data.SBV.Core.Symbolic.html#MonadQuery)\\`, \\`Query a\\` or \\`Symbolic a\\`), while the event handling monad \\`[EventM n a](https://github.com/jtdaugherty/brick/blob/758d8138301ce521214247bd9190abbff7ec0f3d/src/Brick/Types.hs#L128)\\` of brick seems to only allow IO actions.  \n\n\nHow would I best go about unifying these contexts? Is there a way to generalize the event handling of brick to allow for other types of monadic actions to be performed? Or should I rather try to save the state that defines the \\`MonadQuery\\` of SBV in the application state? I found no good way of \"saving\" the context of a MonadQuery to be able to \"resume\" it a later time.",
          "author_fullname": "t2_cx67k",
          "saved": false,
          "mod_reason_title": null,
          "gilded": 0,
          "clicked": false,
          "title": "Combining Brick and SBV monadic contexts",
          "link_flair_richtext": [],
          "subreddit_name_prefixed": "r/haskell",
          "hidden": false,
          "pwls": 6,
          "link_flair_css_class": null,
          "downs": 0,
          "hide_score": false,
          "name": "t3_gmn78x",
          "quarantine": false,
          "link_flair_text_color": "dark",
          "upvote_ratio": 0.92,
          "author_flair_background_color": null,
          "subreddit_type": "public",
          "ups": 9,
          "total_awards_received": 0,
          "media_embed": {},
          "author_flair_template_id": null,
          "is_original_content": false,
          "user_reports": [],
          "secure_media": null,
          "is_reddit_media_domain": false,
          "is_meta": false,
          "category": null,
          "secure_media_embed": {},
          "link_flair_text": null,
          "can_mod_post": false,
          "score": 9,
          "approved_by": null,
          "author_premium": false,
          "thumbnail": "",
          "edited": false,
          "author_flair_css_class": null,
          "author_flair_richtext": [],
          "gildings": {},
          "content_categories": null,
          "is_self": true,
          "mod_note": null,
          "created": 1589918474,
          "link_flair_type": "text",
          "wls": 6,
          "removed_by_category": null,
          "banned_by": null,
          "author_flair_type": "text",
          "domain": "self.haskell",
          "allow_live_comments": false,
          "selftext_html": "&lt;!-- SC_OFF --&gt;&lt;div class=\"md\"&gt;&lt;p&gt;I&amp;#39;ve been beating my head against this issue for a while and thought maybe someone here has a good idea of how to approach this problem.&lt;br/&gt;\nI&amp;#39;m working on a program which has a simple terminal GUI interface using &lt;a href=\"https://github.com/jtdaugherty/brick\"&gt;brick&lt;/a&gt;, and now I want to be able to run SMT queries in the program using the &lt;a href=\"https://hackage.haskell.org/package/sbv-8.6\"&gt;SBV&lt;/a&gt; library. The problem is that the interaction between the program and the SMT solver is being tracked in a monad context (`&lt;a href=\"https://hackage.haskell.org/package/sbv-8.6/docs/src/Data.SBV.Core.Symbolic.html#MonadQuery\"&gt;MonadQuery&lt;/a&gt;`, `Query a` or `Symbolic a`), while the event handling monad `&lt;a href=\"https://github.com/jtdaugherty/brick/blob/758d8138301ce521214247bd9190abbff7ec0f3d/src/Brick/Types.hs#L128\"&gt;EventM n a&lt;/a&gt;` of brick seems to only allow IO actions.  &lt;/p&gt;\n\n&lt;p&gt;How would I best go about unifying these contexts? Is there a way to generalize the event handling of brick to allow for other types of monadic actions to be performed? Or should I rather try to save the state that defines the `MonadQuery` of SBV in the application state? I found no good way of &amp;quot;saving&amp;quot; the context of a MonadQuery to be able to &amp;quot;resume&amp;quot; it a later time.&lt;/p&gt;\n&lt;/div&gt;&lt;!-- SC_ON --&gt;",
          "likes": null,
          "suggested_sort": null,
          "banned_at_utc": null,
          "view_count": null,
          "archived": false,
          "no_follow": false,
          "is_crosspostable": false,
          "pinned": false,
          "over_18": false,
          "all_awardings": [],
          "awarders": [],
          "media_only": false,
          "can_gild": false,
          "spoiler": false,
          "locked": false,
          "author_flair_text": null,
          "treatment_tags": [],
          "visited": false,
          "removed_by": null,
          "num_reports": null,
          "distinguished": null,
          "subreddit_id": "t5_2qh36",
          "mod_reason_by": null,
          "removal_reason": null,
          "link_flair_background_color": "",
          "id": "gmn78x",
          "is_robot_indexable": true,
          "report_reasons": null,
          "author": "Scentable",
          "discussion_type": null,
          "num_comments": 5,
          "send_replies": true,
          "whitelist_status": "all_ads",
          "contest_mode": false,
          "mod_reports": [],
          "author_patreon_flair": false,
          "author_flair_text_color": null,
          "permalink": "/r/haskell/comments/gmn78x/combining_brick_and_sbv_monadic_contexts/",
          "parent_whitelist_status": "all_ads",
          "stickied": false,
          "url": "https://old.reddit.com/r/haskell/comments/gmn78x/combining_brick_and_sbv_monadic_contexts/",
          "subreddit_subscribers": 55194,
          "created_utc": 1589889674,
          "num_crossposts": 0,
          "media": null,
          "is_video": false
        }
      },
      {
        "kind": "t3",
        "data": {
          "approved_at_utc": null,
          "subreddit": "haskell",
          "selftext": "",
          "author_fullname": "t2_fr9sxjo",
          "saved": false,
          "mod_reason_title": null,
          "gilded": 0,
          "clicked": false,
          "title": "I am having difficulty installing Haskero for VSCode",
          "link_flair_richtext": [],
          "subreddit_name_prefixed": "r/haskell",
          "hidden": false,
          "pwls": 6,
          "link_flair_css_class": null,
          "downs": 0,
          "hide_score": false,
          "name": "t3_gmte13",
          "quarantine": false,
          "link_flair_text_color": "dark",
          "upvote_ratio": 0.67,
          "author_flair_background_color": null,
          "subreddit_type": "public",
          "ups": 2,
          "total_awards_received": 0,
          "media_embed": {},
          "author_flair_template_id": null,
          "is_original_content": false,
          "user_reports": [],
          "secure_media": null,
          "is_reddit_media_domain": false,
          "is_meta": false,
          "category": null,
          "secure_media_embed": {},
          "link_flair_text": null,
          "can_mod_post": false,
          "score": 2,
          "approved_by": null,
          "author_premium": false,
          "thumbnail": "",
          "edited": false,
          "author_flair_css_class": null,
          "author_flair_richtext": [],
          "gildings": {},
          "content_categories": null,
          "is_self": false,
          "mod_note": null,
          "crosspost_parent_list": [
            {
              "approved_at_utc": null,
              "subreddit": "vscode",
              "selftext": "I am currently trying to install Haskero for VSCode. I am using [this link](https://gitlab.com/vannnns/haskero/blob/master/client/doc/installation.md) and following the instructions, however I am stuck on step 5. Whenever I type\n\n    stack build intero --copy-compiler-tool\n\ninto the terminal, I get this error message:\n\n    Error: While constructing the build plan, the following exceptions were encountered:\n    \n    In the dependencies for intero-0.1.40:\n        ghc-8.8.3 from stack configuration does not match &gt;=7.8 &amp;&amp; &lt;=8.6.5  (latest matching version is 8.6.5)\n    needed since intero is a build target.\n    \n    Some different approaches to resolving this:\n    \n      * Set 'allow-newer: true' in C:\\sr\\config.yaml to ignore all version constraints and build anyway.\n    \n      * Recommended action: try adding the following to your extra-deps in C:\\sr\\global-project\\stack.yaml:\n    \n    - ghc-8.6.5@sha256:3591225289bdf8cf8f62b10f2aebc9ea3e25a15294545a5312a419e0317784f9,13976\n    \n    Plan construction failed.\n\nI do not know how to handle this. Any  suggestions? Thank you in advance.",
              "author_fullname": "t2_fr9sxjo",
              "saved": false,
              "mod_reason_title": null,
              "gilded": 0,
              "clicked": false,
              "title": "I am having difficulty installing Haskero.",
              "link_flair_richtext": [],
              "subreddit_name_prefixed": "r/vscode",
              "hidden": false,
              "pwls": 6,
              "link_flair_css_class": null,
              "downs": 0,
              "hide_score": false,
              "name": "t3_gm53c8",
              "quarantine": false,
              "link_flair_text_color": "dark",
              "upvote_ratio": 0.75,
              "author_flair_background_color": null,
              "subreddit_type": "public",
              "ups": 4,
              "total_awards_received": 0,
              "media_embed": {},
              "author_flair_template_id": null,
              "is_original_content": true,
              "user_reports": [],
              "secure_media": null,
              "is_reddit_media_domain": false,
              "is_meta": false,
              "category": null,
              "secure_media_embed": {},
              "link_flair_text": null,
              "can_mod_post": false,
              "score": 4,
              "approved_by": null,
              "author_premium": false,
              "thumbnail": "",
              "edited": false,
              "author_flair_css_class": null,
              "author_flair_richtext": [],
              "gildings": {},
              "content_categories": null,
              "is_self": true,
              "mod_note": null,
              "created": 1589849248,
              "link_flair_type": "text",
              "wls": 6,
              "removed_by_category": null,
              "banned_by": null,
              "author_flair_type": "text",
              "domain": "self.vscode",
              "allow_live_comments": false,
              "selftext_html": "&lt;!-- SC_OFF --&gt;&lt;div class=\"md\"&gt;&lt;p&gt;I am currently trying to install Haskero for VSCode. I am using &lt;a href=\"https://gitlab.com/vannnns/haskero/blob/master/client/doc/installation.md\"&gt;this link&lt;/a&gt; and following the instructions, however I am stuck on step 5. Whenever I type&lt;/p&gt;\n\n&lt;pre&gt;&lt;code&gt;stack build intero --copy-compiler-tool\n&lt;/code&gt;&lt;/pre&gt;\n\n&lt;p&gt;into the terminal, I get this error message:&lt;/p&gt;\n\n&lt;pre&gt;&lt;code&gt;Error: While constructing the build plan, the following exceptions were encountered:\n\nIn the dependencies for intero-0.1.40:\n    ghc-8.8.3 from stack configuration does not match &amp;gt;=7.8 &amp;amp;&amp;amp; &amp;lt;=8.6.5  (latest matching version is 8.6.5)\nneeded since intero is a build target.\n\nSome different approaches to resolving this:\n\n  * Set &amp;#39;allow-newer: true&amp;#39; in C:\\sr\\config.yaml to ignore all version constraints and build anyway.\n\n  * Recommended action: try adding the following to your extra-deps in C:\\sr\\global-project\\stack.yaml:\n\n- ghc-8.6.5@sha256:3591225289bdf8cf8f62b10f2aebc9ea3e25a15294545a5312a419e0317784f9,13976\n\nPlan construction failed.\n&lt;/code&gt;&lt;/pre&gt;\n\n&lt;p&gt;I do not know how to handle this. Any  suggestions? Thank you in advance.&lt;/p&gt;\n&lt;/div&gt;&lt;!-- SC_ON --&gt;",
              "likes": null,
              "suggested_sort": null,
              "banned_at_utc": null,
              "view_count": null,
              "archived": false,
              "no_follow": false,
              "is_crosspostable": false,
              "pinned": false,
              "over_18": false,
              "all_awardings": [],
              "awarders": [],
              "media_only": false,
              "can_gild": false,
              "spoiler": false,
              "locked": false,
              "author_flair_text": null,
              "treatment_tags": [],
              "visited": false,
              "removed_by": null,
              "num_reports": null,
              "distinguished": null,
              "subreddit_id": "t5_381yu",
              "mod_reason_by": null,
              "removal_reason": null,
              "link_flair_background_color": "",
              "id": "gm53c8",
              "is_robot_indexable": true,
              "report_reasons": null,
              "author": "The-CPMills",
              "discussion_type": null,
              "num_comments": 0,
              "send_replies": true,
              "whitelist_status": "all_ads",
              "contest_mode": false,
              "mod_reports": [],
              "author_patreon_flair": false,
              "author_flair_text_color": null,
              "permalink": "/r/vscode/comments/gm53c8/i_am_having_difficulty_installing_haskero/",
              "parent_whitelist_status": "all_ads",
              "stickied": false,
              "url": "https://old.reddit.com/r/vscode/comments/gm53c8/i_am_having_difficulty_installing_haskero/",
              "subreddit_subscribers": 40653,
              "created_utc": 1589820448,
              "num_crossposts": 1,
              "media": null,
              "is_video": false
            }
          ],
          "created": 1589939114,
          "link_flair_type": "text",
          "wls": 6,
          "removed_by_category": null,
          "banned_by": null,
          "author_flair_type": "text",
          "domain": "self.vscode",
          "allow_live_comments": false,
          "selftext_html": null,
          "likes": null,
          "suggested_sort": null,
          "banned_at_utc": null,
          "view_count": null,
          "archived": false,
          "no_follow": true,
          "is_crosspostable": false,
          "pinned": false,
          "over_18": false,
          "all_awardings": [],
          "awarders": [],
          "media_only": false,
          "can_gild": false,
          "spoiler": false,
          "locked": false,
          "author_flair_text": null,
          "treatment_tags": [],
          "visited": false,
          "removed_by": null,
          "num_reports": null,
          "distinguished": null,
          "subreddit_id": "t5_2qh36",
          "mod_reason_by": null,
          "removal_reason": null,
          "link_flair_background_color": "",
          "id": "gmte13",
          "is_robot_indexable": true,
          "report_reasons": null,
          "author": "The-CPMills",
          "discussion_type": null,
          "num_comments": 5,
          "send_replies": true,
          "whitelist_status": "all_ads",
          "contest_mode": false,
          "mod_reports": [],
          "author_patreon_flair": false,
          "crosspost_parent": "t3_gm53c8",
          "author_flair_text_color": null,
          "permalink": "/r/haskell/comments/gmte13/i_am_having_difficulty_installing_haskero_for/",
          "parent_whitelist_status": "all_ads",
          "stickied": false,
          "url": "/r/vscode/comments/gm53c8/i_am_having_difficulty_installing_haskero/",
          "subreddit_subscribers": 55194,
          "created_utc": 1589910314,
          "num_crossposts": 0,
          "media": null,
          "is_video": false
        }
      },
      {
        "kind": "t3",
        "data": {
          "approved_at_utc": null,
          "subreddit": "haskell",
          "selftext": "",
          "author_fullname": "t2_7d9ta",
          "saved": false,
          "mod_reason_title": null,
          "gilded": 0,
          "clicked": false,
          "title": "[GHC Blog] The state of GHC on ARM",
          "link_flair_richtext": [],
          "subreddit_name_prefixed": "r/haskell",
          "hidden": false,
          "pwls": 6,
          "link_flair_css_class": null,
          "downs": 0,
          "hide_score": false,
          "name": "t3_gmbfyr",
          "quarantine": false,
          "link_flair_text_color": "dark",
          "upvote_ratio": 0.98,
          "author_flair_background_color": null,
          "subreddit_type": "public",
          "ups": 77,
          "total_awards_received": 0,
          "media_embed": {},
          "author_flair_template_id": null,
          "is_original_content": false,
          "user_reports": [],
          "secure_media": null,
          "is_reddit_media_domain": false,
          "is_meta": false,
          "category": null,
          "secure_media_embed": {},
          "link_flair_text": null,
          "can_mod_post": false,
          "score": 77,
          "approved_by": null,
          "author_premium": false,
          "thumbnail": "",
          "edited": false,
          "author_flair_css_class": null,
          "author_flair_richtext": [],
          "gildings": {},
          "content_categories": null,
          "is_self": false,
          "mod_note": null,
          "created": 1589868527,
          "link_flair_type": "text",
          "wls": 6,
          "removed_by_category": null,
          "banned_by": null,
          "author_flair_type": "text",
          "domain": "haskell.org",
          "allow_live_comments": false,
          "selftext_html": null,
          "likes": null,
          "suggested_sort": null,
          "banned_at_utc": null,
          "view_count": null,
          "archived": false,
          "no_follow": false,
          "is_crosspostable": false,
          "pinned": false,
          "over_18": false,
          "all_awardings": [],
          "awarders": [],
          "media_only": false,
          "can_gild": false,
          "spoiler": false,
          "locked": false,
          "author_flair_text": null,
          "treatment_tags": [],
          "visited": false,
          "removed_by": null,
          "num_reports": null,
          "distinguished": null,
          "subreddit_id": "t5_2qh36",
          "mod_reason_by": null,
          "removal_reason": null,
          "link_flair_background_color": "",
          "id": "gmbfyr",
          "is_robot_indexable": true,
          "report_reasons": null,
          "author": "bgamari",
          "discussion_type": null,
          "num_comments": 9,
          "send_replies": true,
          "whitelist_status": "all_ads",
          "contest_mode": false,
          "mod_reports": [],
          "author_patreon_flair": false,
          "author_flair_text_color": null,
          "permalink": "/r/haskell/comments/gmbfyr/ghc_blog_the_state_of_ghc_on_arm/",
          "parent_whitelist_status": "all_ads",
          "stickied": false,
          "url": "https://www.haskell.org/ghc/blog/20200515-ghc-on-arm.html",
          "subreddit_subscribers": 55194,
          "created_utc": 1589839727,
          "num_crossposts": 1,
          "media": null,
          "is_video": false
        }
      },
      {
        "kind": "t3",
        "data": {
          "approved_at_utc": null,
          "subreddit": "haskell",
          "selftext": "I'm trying to build the board for the Peg Solitaire game but I'm stuck. I hope you can help me. The following code runs and generates a square of 3 on 3 circles. How could I make 3 more such squares but put them in other positions? I use the Gloss library. \n\n&amp;#x200B;\n\n`module Main(main) where` \n\n`import Graphics.Gloss` \n\n`import Graphics.Gloss.Data.ViewPort` \n\n`import` [`Graphics.Gloss.Interface.Pure.Game`](https://Graphics.Gloss.Interface.Pure.Game)\n\n `import Data.List`  \n\n`width, height, offset :: Int` \n\n`width = 400` \n\n`height = 400`\n\n `offset = 100`  \n\n`window :: Display window = InWindow \"Peg Solitaire\" (width, height) (offset, offset)`\n\n  `background :: Color` \n\n`background = white`  \n\n`drawing :: Picture` \n\n`drawing = Pictures [ (translate (x * 40) (y * 40) $ circleSolid 12)| x&lt;-[-1..1], y&lt;-[2..4] ]`  \n\n`main = display window background drawing`",
          "author_fullname": "t2_tewbqxp",
          "saved": false,
          "mod_reason_title": null,
          "gilded": 0,
          "clicked": false,
          "title": "Drawing the game board in Haskell",
          "link_flair_richtext": [],
          "subreddit_name_prefixed": "r/haskell",
          "hidden": false,
          "pwls": 6,
          "link_flair_css_class": null,
          "downs": 0,
          "hide_score": false,
          "name": "t3_gmsipz",
          "quarantine": false,
          "link_flair_text_color": "dark",
          "upvote_ratio": 0.75,
          "author_flair_background_color": null,
          "subreddit_type": "public",
          "ups": 4,
          "total_awards_received": 0,
          "media_embed": {},
          "author_flair_template_id": null,
          "is_original_content": false,
          "user_reports": [],
          "secure_media": null,
          "is_reddit_media_domain": false,
          "is_meta": false,
          "category": null,
          "secure_media_embed": {},
          "link_flair_text": null,
          "can_mod_post": false,
          "score": 4,
          "approved_by": null,
          "author_premium": false,
          "thumbnail": "",
          "edited": false,
          "author_flair_css_class": null,
          "author_flair_richtext": [],
          "gildings": {},
          "content_categories": null,
          "is_self": true,
          "mod_note": null,
          "created": 1589936485,
          "link_flair_type": "text",
          "wls": 6,
          "removed_by_category": null,
          "banned_by": null,
          "author_flair_type": "text",
          "domain": "self.haskell",
          "allow_live_comments": false,
          "selftext_html": "&lt;!-- SC_OFF --&gt;&lt;div class=\"md\"&gt;&lt;p&gt;I&amp;#39;m trying to build the board for the Peg Solitaire game but I&amp;#39;m stuck. I hope you can help me. The following code runs and generates a square of 3 on 3 circles. How could I make 3 more such squares but put them in other positions? I use the Gloss library. &lt;/p&gt;\n\n&lt;p&gt;&amp;#x200B;&lt;/p&gt;\n\n&lt;p&gt;&lt;code&gt;module Main(main) where&lt;/code&gt; &lt;/p&gt;\n\n&lt;p&gt;&lt;code&gt;import Graphics.Gloss&lt;/code&gt; &lt;/p&gt;\n\n&lt;p&gt;&lt;code&gt;import Graphics.Gloss.Data.ViewPort&lt;/code&gt; &lt;/p&gt;\n\n&lt;p&gt;&lt;code&gt;import&lt;/code&gt; &lt;a href=\"https://Graphics.Gloss.Interface.Pure.Game\"&gt;&lt;code&gt;Graphics.Gloss.Interface.Pure.Game&lt;/code&gt;&lt;/a&gt;&lt;/p&gt;\n\n&lt;p&gt;&lt;code&gt;import Data.List&lt;/code&gt;  &lt;/p&gt;\n\n&lt;p&gt;&lt;code&gt;width, height, offset :: Int&lt;/code&gt; &lt;/p&gt;\n\n&lt;p&gt;&lt;code&gt;width = 400&lt;/code&gt; &lt;/p&gt;\n\n&lt;p&gt;&lt;code&gt;height = 400&lt;/code&gt;&lt;/p&gt;\n\n&lt;p&gt;&lt;code&gt;offset = 100&lt;/code&gt;  &lt;/p&gt;\n\n&lt;p&gt;&lt;code&gt;window :: Display window = InWindow &amp;quot;Peg Solitaire&amp;quot; (width, height) (offset, offset)&lt;/code&gt;&lt;/p&gt;\n\n&lt;p&gt;&lt;code&gt;background :: Color&lt;/code&gt; &lt;/p&gt;\n\n&lt;p&gt;&lt;code&gt;background = white&lt;/code&gt;  &lt;/p&gt;\n\n&lt;p&gt;&lt;code&gt;drawing :: Picture&lt;/code&gt; &lt;/p&gt;\n\n&lt;p&gt;&lt;code&gt;drawing = Pictures [ (translate (x * 40) (y * 40) $ circleSolid 12)| x&amp;lt;-[-1..1], y&amp;lt;-[2..4] ]&lt;/code&gt;  &lt;/p&gt;\n\n&lt;p&gt;&lt;code&gt;main = display window background drawing&lt;/code&gt;&lt;/p&gt;\n&lt;/div&gt;&lt;!-- SC_ON --&gt;",
          "likes": null,
          "suggested_sort": null,
          "banned_at_utc": null,
          "view_count": null,
          "archived": false,
          "no_follow": true,
          "is_crosspostable": false,
          "pinned": false,
          "over_18": false,
          "all_awardings": [],
          "awarders": [],
          "media_only": false,
          "can_gild": false,
          "spoiler": false,
          "locked": false,
          "author_flair_text": null,
          "treatment_tags": [],
          "visited": false,
          "removed_by": null,
          "num_reports": null,
          "distinguished": null,
          "subreddit_id": "t5_2qh36",
          "mod_reason_by": null,
          "removal_reason": null,
          "link_flair_background_color": "",
          "id": "gmsipz",
          "is_robot_indexable": true,
          "report_reasons": null,
          "author": "radu23",
          "discussion_type": null,
          "num_comments": 11,
          "send_replies": true,
          "whitelist_status": "all_ads",
          "contest_mode": false,
          "mod_reports": [],
          "author_patreon_flair": false,
          "author_flair_text_color": null,
          "permalink": "/r/haskell/comments/gmsipz/drawing_the_game_board_in_haskell/",
          "parent_whitelist_status": "all_ads",
          "stickied": false,
          "url": "https://old.reddit.com/r/haskell/comments/gmsipz/drawing_the_game_board_in_haskell/",
          "subreddit_subscribers": 55194,
          "created_utc": 1589907685,
          "num_crossposts": 0,
          "media": null,
          "is_video": false
        }
      },
      {
        "kind": "t3",
        "data": {
          "approved_at_utc": null,
          "subreddit": "haskell",
          "selftext": "",
          "author_fullname": "t2_jxviuup",
          "saved": false,
          "mod_reason_title": null,
          "gilded": 0,
          "clicked": false,
          "title": "Presentation on Purely Functional Data Structures - Donnacha Oisín Kidney",
          "link_flair_richtext": [],
          "subreddit_name_prefixed": "r/haskell",
          "hidden": false,
          "pwls": 6,
          "link_flair_css_class": null,
          "downs": 0,
          "hide_score": false,
          "name": "t3_gmen1i",
          "quarantine": false,
          "link_flair_text_color": "dark",
          "upvote_ratio": 1,
          "author_flair_background_color": null,
          "subreddit_type": "public",
          "ups": 27,
          "total_awards_received": 0,
          "media_embed": {},
          "author_flair_template_id": null,
          "is_original_content": false,
          "user_reports": [],
          "secure_media": null,
          "is_reddit_media_domain": false,
          "is_meta": false,
          "category": null,
          "secure_media_embed": {},
          "link_flair_text": null,
          "can_mod_post": false,
          "score": 27,
          "approved_by": null,
          "author_premium": false,
          "thumbnail": "",
          "edited": false,
          "author_flair_css_class": null,
          "author_flair_richtext": [],
          "gildings": {},
          "content_categories": null,
          "is_self": false,
          "mod_note": null,
          "created": 1589879479,
          "link_flair_type": "text",
          "wls": 6,
          "removed_by_category": null,
          "banned_by": null,
          "author_flair_type": "text",
          "domain": "doisinkidney.com",
          "allow_live_comments": false,
          "selftext_html": null,
          "likes": null,
          "suggested_sort": null,
          "banned_at_utc": null,
          "view_count": null,
          "archived": false,
          "no_follow": false,
          "is_crosspostable": false,
          "pinned": false,
          "over_18": false,
          "all_awardings": [],
          "awarders": [],
          "media_only": false,
          "can_gild": false,
          "spoiler": false,
          "locked": false,
          "author_flair_text": null,
          "treatment_tags": [],
          "visited": false,
          "removed_by": null,
          "num_reports": null,
          "distinguished": null,
          "subreddit_id": "t5_2qh36",
          "mod_reason_by": null,
          "removal_reason": null,
          "link_flair_background_color": "",
          "id": "gmen1i",
          "is_robot_indexable": true,
          "report_reasons": null,
          "author": "iedoub",
          "discussion_type": null,
          "num_comments": 12,
          "send_replies": true,
          "whitelist_status": "all_ads",
          "contest_mode": false,
          "mod_reports": [],
          "author_patreon_flair": false,
          "author_flair_text_color": null,
          "permalink": "/r/haskell/comments/gmen1i/presentation_on_purely_functional_data_structures/",
          "parent_whitelist_status": "all_ads",
          "stickied": false,
          "url": "https://doisinkidney.com/posts/2020-05-19-purely-functional-data-structures-slides.html",
          "subreddit_subscribers": 55194,
          "created_utc": 1589850679,
          "num_crossposts": 0,
          "media": null,
          "is_video": false
        }
      },
      {
        "kind": "t3",
        "data": {
          "approved_at_utc": null,
          "subreddit": "haskell",
          "selftext": "I created a project with stack. Most of the time during the project I used the .cabal file to add dependencies. And that worked fine. However when adding the dependency for a sat-solver I got the following error\n\n```\nminisat-solver needed, but the stack configuration has no specified version  (latest matching version\n               is 0.1)\n```\n\nTo solve this error I added the line\n\n```\n - minisat-solver-0.1@sha256:e2ff11b1ca8c66e43f8bb2e04f21bd1b812efb94ff215d74f998c928e7e92dcd,5210\n```\n\nto my .yaml file.\n\nNow whenever I use `stack build` I get the error\n\n```\n....cabal was modified manually Ignoring ...package.yaml in favor of the cabal file.\nIf you want to use the package.yaml file instead of the cabal file,\nthen please delete the cabal file.\n```\n\nHow should I solve this? Should I just delete the .cabal file? What changes should I make to .yaml file\n\n--\n\nThe .yaml flie\n\n```\n# This file was automatically generated by 'stack init'\n#\n# Some commonly used options have been documented as comments in this file.\n# For advanced use and comprehensive documentation of the format, please see:\n# https://docs.haskellstack.org/en/stable/yaml_configuration/\n\n# Resolver to choose a 'specific' stackage snapshot or a compiler version.\n# A snapshot resolver dictates the compiler version and the set of packages\n# to be used for project dependencies. For example:\n#\n# resolver: lts-3.5\n# resolver: nightly-2015-09-21\n# resolver: ghc-7.10.2\n#\n# The location of a snapshot can be provided as a file or url. Stack assumes\n# a snapshot provided as a file might change, whereas a url resource does not.\n#\n# resolver: ./custom-snapshot.yaml\n# resolver: https://example.com/snapshots/2018-01-01.yaml\nresolver: lts-14.20\n\n# User packages to be built.\n# Various formats can be used as shown in the example below.\n#\n# packages:\n# - some-directory\n# - https://example.com/foo/bar/baz-0.0.2.tar.gz\n#   subdirs:\n#   - auto-update\n#   - wai\npackages:\n- .\n# Dependency packages to be pulled from upstream that are not in the resolver.\n# These entries can reference officially published versions as well as\n# forks / in-progress versions pinned to a git hash. For example:\n#\n# extra-deps:\n# - acme-missiles-0.3\n# - git: https://github.com/commercialhaskell/stack.git\n#   commit: e7b331f14bcffb8367cd58fbfc8b40ec7642100a\n#\n# extra-deps: []\n\n# Override default flag values for local packages and extra-deps\n# flags: {}\n\n# Extra package databases containing global packages\n# extra-package-dbs: []\n\n# Control whether we use the GHC we find on the path\n# system-ghc: true\n#\n# Require a specific version of stack, using version ranges\n# require-stack-version: -any # Default\n# require-stack-version: \"&gt;=2.1\"\n#\n# Override the architecture used by stack, especially useful on Windows\n# arch: i386\n# arch: x86_64\n#\n# Extra directories used by stack for building\n# extra-include-dirs: [/path/to/dir]\n# extra-lib-dirs: [/path/to/dir]\n#\n# Allow a newer minor version of GHC than the snapshot specifies\n# compiler-check: newer-minor\n\nextra-deps:\n - minisat-solver-0.1@sha256:e2ff11b1ca8c66e43f8bb2e04f21bd1b812efb94ff215d74f998c928e7e92dcd,5210\n\n```\n\nThe cabal file\n\n```\ncabal-version: 1.12\n\n-- This file has been generated from package.yaml by hpack version 0.31.2.\n--\n-- see: https://github.com/sol/hpack\n--\n-- hash: 9e4c1b8d2c640f6364c7abf13e184823a0c4b7959a05310c93a9b6ff92efad16\n\nname:           dtl-model-checking\nversion:        0.1.0.0\ndescription:    Please see the README on GitHub at &lt;https://github.com/githubuser/dtl-model-checking#readme&gt;\nhomepage:       https://github.com/githubuser/dtl-model-checking#readme\nbug-reports:    https://github.com/githubuser/dtl-model-checking/issues\nauthor:         Author name here\nmaintainer:     example@example.com\ncopyright:      2020 Author name here\nlicense:        BSD3\nlicense-file:   LICENSE\nbuild-type:     Simple\nextra-source-files:\n    README.md\n    ChangeLog.md\n\nsource-repository head\n  type: git\n  location: https://github.com/githubuser/dtl-model-checking\n\nlibrary\n  exposed-modules:\n      Automaton\n      DTLFormula\n      AutomataTheoreticApproach\n      DTS\n      NBA\n      GNBA\n      Ielementary\n      CommonTypes\n      Utils\n      ExampleInstances\n      BMC\n  other-modules:\n      Paths_dtl_model_checking\n  hs-source-dirs:\n      src\n  build-depends:\n      base &gt;=4.7 &amp;&amp; &lt;5\n    , containers\n    , random\n    , minisat-solver &gt;= 0.1\n  default-language: Haskell2010\n\nexecutable dtl-model-checking-exe\n  main-is: Main.hs\n  other-modules:\n      Paths_dtl_model_checking\n  hs-source-dirs:\n      app\n  ghc-options: -O -threaded -rtsopts -with-rtsopts=-N\n  build-depends:\n      base &gt;=4.7 &amp;&amp; &lt;5\n    , dtl-model-checking\n    , containers\n    , random\n  default-language: Haskell2010\n\ntest-suite dtl-model-checking-test\n  type: exitcode-stdio-1.0\n  main-is: Spec.hs\n  other-modules:\n      Paths_dtl_model_checking\n  hs-source-dirs:\n      test\n  ghc-options: -O -threaded -rtsopts -with-rtsopts=-N\n  build-depends:\n      base &gt;=4.7 &amp;&amp; &lt;5\n    , dtl-model-checking\n    , containers\n    , hspec\n    , random\n  default-language: Haskell2010\n\nbenchmark dtl-model-checking-benchmark\n  type: exitcode-stdio-1.0 \n  main-is: Bench.hs\n  other-modules:\n      Paths_dtl_model_checking\n  hs-source-dirs:\n      benchmark\n  ghc-options: -O -threaded -fforce-recomp -rtsopts -with-rtsopts=-N\n  build-depends: base &gt;=4.7 &amp;&amp; &lt;5, dtl-model-checking, containers, criterion, random\n  default-language: Haskell2010\n```",
          "author_fullname": "t2_u7qgp4w",
          "saved": false,
          "mod_reason_title": null,
          "gilded": 0,
          "clicked": false,
          "title": "Error/warning on stack build",
          "link_flair_richtext": [],
          "subreddit_name_prefixed": "r/haskell",
          "hidden": false,
          "pwls": 6,
          "link_flair_css_class": null,
          "downs": 0,
          "hide_score": false,
          "name": "t3_gmoik7",
          "quarantine": false,
          "link_flair_text_color": "dark",
          "upvote_ratio": 0.5,
          "author_flair_background_color": null,
          "subreddit_type": "public",
          "ups": 0,
          "total_awards_received": 0,
          "media_embed": {},
          "author_flair_template_id": null,
          "is_original_content": false,
          "user_reports": [],
          "secure_media": null,
          "is_reddit_media_domain": false,
          "is_meta": false,
          "category": null,
          "secure_media_embed": {},
          "link_flair_text": null,
          "can_mod_post": false,
          "score": 0,
          "approved_by": null,
          "author_premium": false,
          "thumbnail": "",
          "edited": false,
          "author_flair_css_class": null,
          "author_flair_richtext": [],
          "gildings": {},
          "content_categories": null,
          "is_self": true,
          "mod_note": null,
          "created": 1589923554,
          "link_flair_type": "text",
          "wls": 6,
          "removed_by_category": null,
          "banned_by": null,
          "author_flair_type": "text",
          "domain": "self.haskell",
          "allow_live_comments": false,
          "selftext_html": "&lt;!-- SC_OFF --&gt;&lt;div class=\"md\"&gt;&lt;p&gt;I created a project with stack. Most of the time during the project I used the .cabal file to add dependencies. And that worked fine. However when adding the dependency for a sat-solver I got the following error&lt;/p&gt;\n\n&lt;p&gt;&lt;code&gt;\nminisat-solver needed, but the stack configuration has no specified version  (latest matching version\n               is 0.1)\n&lt;/code&gt;&lt;/p&gt;\n\n&lt;p&gt;To solve this error I added the line&lt;/p&gt;\n\n&lt;p&gt;&lt;code&gt;\n - minisat-solver-0.1@sha256:e2ff11b1ca8c66e43f8bb2e04f21bd1b812efb94ff215d74f998c928e7e92dcd,5210\n&lt;/code&gt;&lt;/p&gt;\n\n&lt;p&gt;to my .yaml file.&lt;/p&gt;\n\n&lt;p&gt;Now whenever I use &lt;code&gt;stack build&lt;/code&gt; I get the error&lt;/p&gt;\n\n&lt;p&gt;&lt;code&gt;\n....cabal was modified manually Ignoring ...package.yaml in favor of the cabal file.\nIf you want to use the package.yaml file instead of the cabal file,\nthen please delete the cabal file.\n&lt;/code&gt;&lt;/p&gt;\n\n&lt;p&gt;How should I solve this? Should I just delete the .cabal file? What changes should I make to .yaml file&lt;/p&gt;\n\n&lt;h2&gt;&lt;/h2&gt;\n\n&lt;p&gt;The .yaml flie&lt;/p&gt;\n\n&lt;p&gt;```&lt;/p&gt;\n\n&lt;h1&gt;This file was automatically generated by &amp;#39;stack init&amp;#39;&lt;/h1&gt;\n\n&lt;h1&gt;Some commonly used options have been documented as comments in this file.&lt;/h1&gt;\n\n&lt;h1&gt;For advanced use and comprehensive documentation of the format, please see:&lt;/h1&gt;\n\n&lt;h1&gt;&lt;a href=\"https://docs.haskellstack.org/en/stable/yaml_configuration/\"&gt;https://docs.haskellstack.org/en/stable/yaml_configuration/&lt;/a&gt;&lt;/h1&gt;\n\n&lt;h1&gt;Resolver to choose a &amp;#39;specific&amp;#39; stackage snapshot or a compiler version.&lt;/h1&gt;\n\n&lt;h1&gt;A snapshot resolver dictates the compiler version and the set of packages&lt;/h1&gt;\n\n&lt;h1&gt;to be used for project dependencies. For example:&lt;/h1&gt;\n\n&lt;h1&gt;resolver: lts-3.5&lt;/h1&gt;\n\n&lt;h1&gt;resolver: nightly-2015-09-21&lt;/h1&gt;\n\n&lt;h1&gt;resolver: ghc-7.10.2&lt;/h1&gt;\n\n&lt;h1&gt;The location of a snapshot can be provided as a file or url. Stack assumes&lt;/h1&gt;\n\n&lt;h1&gt;a snapshot provided as a file might change, whereas a url resource does not.&lt;/h1&gt;\n\n&lt;h1&gt;resolver: ./custom-snapshot.yaml&lt;/h1&gt;\n\n&lt;h1&gt;resolver: &lt;a href=\"https://example.com/snapshots/2018-01-01.yaml\"&gt;https://example.com/snapshots/2018-01-01.yaml&lt;/a&gt;&lt;/h1&gt;\n\n&lt;p&gt;resolver: lts-14.20&lt;/p&gt;\n\n&lt;h1&gt;User packages to be built.&lt;/h1&gt;\n\n&lt;h1&gt;Various formats can be used as shown in the example below.&lt;/h1&gt;\n\n&lt;h1&gt;packages:&lt;/h1&gt;\n\n&lt;h1&gt;- some-directory&lt;/h1&gt;\n\n&lt;h1&gt;- &lt;a href=\"https://example.com/foo/bar/baz-0.0.2.tar.gz\"&gt;https://example.com/foo/bar/baz-0.0.2.tar.gz&lt;/a&gt;&lt;/h1&gt;\n\n&lt;h1&gt;subdirs:&lt;/h1&gt;\n\n&lt;h1&gt;- auto-update&lt;/h1&gt;\n\n&lt;h1&gt;- wai&lt;/h1&gt;\n\n&lt;p&gt;packages:\n- .&lt;/p&gt;\n\n&lt;h1&gt;Dependency packages to be pulled from upstream that are not in the resolver.&lt;/h1&gt;\n\n&lt;h1&gt;These entries can reference officially published versions as well as&lt;/h1&gt;\n\n&lt;h1&gt;forks / in-progress versions pinned to a git hash. For example:&lt;/h1&gt;\n\n&lt;h1&gt;extra-deps:&lt;/h1&gt;\n\n&lt;h1&gt;- acme-missiles-0.3&lt;/h1&gt;\n\n&lt;h1&gt;- git: &lt;a href=\"https://github.com/commercialhaskell/stack.git\"&gt;https://github.com/commercialhaskell/stack.git&lt;/a&gt;&lt;/h1&gt;\n\n&lt;h1&gt;commit: e7b331f14bcffb8367cd58fbfc8b40ec7642100a&lt;/h1&gt;\n\n&lt;h1&gt;extra-deps: []&lt;/h1&gt;\n\n&lt;h1&gt;Override default flag values for local packages and extra-deps&lt;/h1&gt;\n\n&lt;h1&gt;flags: {}&lt;/h1&gt;\n\n&lt;h1&gt;Extra package databases containing global packages&lt;/h1&gt;\n\n&lt;h1&gt;extra-package-dbs: []&lt;/h1&gt;\n\n&lt;h1&gt;Control whether we use the GHC we find on the path&lt;/h1&gt;\n\n&lt;h1&gt;system-ghc: true&lt;/h1&gt;\n\n&lt;h1&gt;Require a specific version of stack, using version ranges&lt;/h1&gt;\n\n&lt;h1&gt;require-stack-version: -any # Default&lt;/h1&gt;\n\n&lt;h1&gt;require-stack-version: &amp;quot;&amp;gt;=2.1&amp;quot;&lt;/h1&gt;\n\n&lt;h1&gt;Override the architecture used by stack, especially useful on Windows&lt;/h1&gt;\n\n&lt;h1&gt;arch: i386&lt;/h1&gt;\n\n&lt;h1&gt;arch: x86_64&lt;/h1&gt;\n\n&lt;h1&gt;Extra directories used by stack for building&lt;/h1&gt;\n\n&lt;h1&gt;extra-include-dirs: [/path/to/dir]&lt;/h1&gt;\n\n&lt;h1&gt;extra-lib-dirs: [/path/to/dir]&lt;/h1&gt;\n\n&lt;h1&gt;Allow a newer minor version of GHC than the snapshot specifies&lt;/h1&gt;\n\n&lt;h1&gt;compiler-check: newer-minor&lt;/h1&gt;\n\n&lt;p&gt;extra-deps:\n - minisat-solver-0.1@sha256:e2ff11b1ca8c66e43f8bb2e04f21bd1b812efb94ff215d74f998c928e7e92dcd,5210&lt;/p&gt;\n\n&lt;p&gt;```&lt;/p&gt;\n\n&lt;p&gt;The cabal file&lt;/p&gt;\n\n&lt;p&gt;```\ncabal-version: 1.12&lt;/p&gt;\n\n&lt;h2&gt;-- This file has been generated from package.yaml by hpack version 0.31.2.&lt;/h2&gt;\n\n&lt;h2&gt;-- see: &lt;a href=\"https://github.com/sol/hpack\"&gt;https://github.com/sol/hpack&lt;/a&gt;&lt;/h2&gt;\n\n&lt;p&gt;-- hash: 9e4c1b8d2c640f6364c7abf13e184823a0c4b7959a05310c93a9b6ff92efad16&lt;/p&gt;\n\n&lt;p&gt;name:           dtl-model-checking\nversion:        0.1.0.0\ndescription:    Please see the README on GitHub at &lt;a href=\"https://github.com/githubuser/dtl-model-checking#readme\"&gt;https://github.com/githubuser/dtl-model-checking#readme&lt;/a&gt;\nhomepage:       &lt;a href=\"https://github.com/githubuser/dtl-model-checking#readme\"&gt;https://github.com/githubuser/dtl-model-checking#readme&lt;/a&gt;\nbug-reports:    &lt;a href=\"https://github.com/githubuser/dtl-model-checking/issues\"&gt;https://github.com/githubuser/dtl-model-checking/issues&lt;/a&gt;\nauthor:         Author name here\nmaintainer:     &lt;a href=\"mailto:example@example.com\"&gt;example@example.com&lt;/a&gt;\ncopyright:      2020 Author name here\nlicense:        BSD3\nlicense-file:   LICENSE\nbuild-type:     Simple\nextra-source-files:\n    README.md\n    ChangeLog.md&lt;/p&gt;\n\n&lt;p&gt;source-repository head\n  type: git\n  location: &lt;a href=\"https://github.com/githubuser/dtl-model-checking\"&gt;https://github.com/githubuser/dtl-model-checking&lt;/a&gt;&lt;/p&gt;\n\n&lt;p&gt;library\n  exposed-modules:\n      Automaton\n      DTLFormula\n      AutomataTheoreticApproach\n      DTS\n      NBA\n      GNBA\n      Ielementary\n      CommonTypes\n      Utils\n      ExampleInstances\n      BMC\n  other-modules:\n      Paths_dtl_model_checking\n  hs-source-dirs:\n      src\n  build-depends:\n      base &amp;gt;=4.7 &amp;amp;&amp;amp; &amp;lt;5\n    , containers\n    , random\n    , minisat-solver &amp;gt;= 0.1\n  default-language: Haskell2010&lt;/p&gt;\n\n&lt;p&gt;executable dtl-model-checking-exe\n  main-is: Main.hs\n  other-modules:\n      Paths_dtl_model_checking\n  hs-source-dirs:\n      app\n  ghc-options: -O -threaded -rtsopts -with-rtsopts=-N\n  build-depends:\n      base &amp;gt;=4.7 &amp;amp;&amp;amp; &amp;lt;5\n    , dtl-model-checking\n    , containers\n    , random\n  default-language: Haskell2010&lt;/p&gt;\n\n&lt;p&gt;test-suite dtl-model-checking-test\n  type: exitcode-stdio-1.0\n  main-is: Spec.hs\n  other-modules:\n      Paths_dtl_model_checking\n  hs-source-dirs:\n      test\n  ghc-options: -O -threaded -rtsopts -with-rtsopts=-N\n  build-depends:\n      base &amp;gt;=4.7 &amp;amp;&amp;amp; &amp;lt;5\n    , dtl-model-checking\n    , containers\n    , hspec\n    , random\n  default-language: Haskell2010&lt;/p&gt;\n\n&lt;p&gt;benchmark dtl-model-checking-benchmark\n  type: exitcode-stdio-1.0 \n  main-is: Bench.hs\n  other-modules:\n      Paths_dtl_model_checking\n  hs-source-dirs:\n      benchmark\n  ghc-options: -O -threaded -fforce-recomp -rtsopts -with-rtsopts=-N\n  build-depends: base &amp;gt;=4.7 &amp;amp;&amp;amp; &amp;lt;5, dtl-model-checking, containers, criterion, random\n  default-language: Haskell2010\n```&lt;/p&gt;\n&lt;/div&gt;&lt;!-- SC_ON --&gt;",
          "likes": null,
          "suggested_sort": null,
          "banned_at_utc": null,
          "view_count": null,
          "archived": false,
          "no_follow": true,
          "is_crosspostable": false,
          "pinned": false,
          "over_18": false,
          "all_awardings": [],
          "awarders": [],
          "media_only": false,
          "can_gild": false,
          "spoiler": false,
          "locked": false,
          "author_flair_text": null,
          "treatment_tags": [],
          "visited": false,
          "removed_by": null,
          "num_reports": null,
          "distinguished": null,
          "subreddit_id": "t5_2qh36",
          "mod_reason_by": null,
          "removal_reason": null,
          "link_flair_background_color": "",
          "id": "gmoik7",
          "is_robot_indexable": true,
          "report_reasons": null,
          "author": "augustoperes",
          "discussion_type": null,
          "num_comments": 2,
          "send_replies": true,
          "whitelist_status": "all_ads",
          "contest_mode": false,
          "mod_reports": [],
          "author_patreon_flair": false,
          "author_flair_text_color": null,
          "permalink": "/r/haskell/comments/gmoik7/errorwarning_on_stack_build/",
          "parent_whitelist_status": "all_ads",
          "stickied": false,
          "url": "https://old.reddit.com/r/haskell/comments/gmoik7/errorwarning_on_stack_build/",
          "subreddit_subscribers": 55194,
          "created_utc": 1589894754,
          "num_crossposts": 0,
          "media": null,
          "is_video": false
        }
      },
      {
        "kind": "t3",
        "data": {
          "approved_at_utc": null,
          "subreddit": "haskell",
          "selftext": "Do you have any examples of libraries in other languages or language features, which really should have implemented a well-known concept (Monoid, Monad, Alternative, whatever), but they fell short because they (probably) didn't know the concept? For example a broken law, a missing function, over-complicated function types, etc.\n\nI encountered multiple such examples, and they always grind my gears. But for the life of me, I can't remember any of them now.",
          "author_fullname": "t2_b7rje",
          "saved": false,
          "mod_reason_title": null,
          "gilded": 0,
          "clicked": false,
          "title": "Examples of Incorrect Abstractions in Other Languages",
          "link_flair_richtext": [],
          "subreddit_name_prefixed": "r/haskell",
          "hidden": false,
          "pwls": 6,
          "link_flair_css_class": null,
          "downs": 0,
          "hide_score": false,
          "name": "t3_glz389",
          "quarantine": false,
          "link_flair_text_color": "dark",
          "upvote_ratio": 0.97,
          "author_flair_background_color": null,
          "subreddit_type": "public",
          "ups": 103,
          "total_awards_received": 0,
          "media_embed": {},
          "author_flair_template_id": null,
          "is_original_content": false,
          "user_reports": [],
          "secure_media": null,
          "is_reddit_media_domain": false,
          "is_meta": false,
          "category": null,
          "secure_media_embed": {},
          "link_flair_text": null,
          "can_mod_post": false,
          "score": 103,
          "approved_by": null,
          "author_premium": false,
          "thumbnail": "",
          "edited": false,
          "author_flair_css_class": null,
          "author_flair_richtext": [],
          "gildings": {},
          "content_categories": null,
          "is_self": true,
          "mod_note": null,
          "created": 1589827048,
          "link_flair_type": "text",
          "wls": 6,
          "removed_by_category": null,
          "banned_by": null,
          "author_flair_type": "text",
          "domain": "self.haskell",
          "allow_live_comments": false,
          "selftext_html": "&lt;!-- SC_OFF --&gt;&lt;div class=\"md\"&gt;&lt;p&gt;Do you have any examples of libraries in other languages or language features, which really should have implemented a well-known concept (Monoid, Monad, Alternative, whatever), but they fell short because they (probably) didn&amp;#39;t know the concept? For example a broken law, a missing function, over-complicated function types, etc.&lt;/p&gt;\n\n&lt;p&gt;I encountered multiple such examples, and they always grind my gears. But for the life of me, I can&amp;#39;t remember any of them now.&lt;/p&gt;\n&lt;/div&gt;&lt;!-- SC_ON --&gt;",
          "likes": null,
          "suggested_sort": null,
          "banned_at_utc": null,
          "view_count": null,
          "archived": false,
          "no_follow": false,
          "is_crosspostable": false,
          "pinned": false,
          "over_18": false,
          "all_awardings": [],
          "awarders": [],
          "media_only": false,
          "can_gild": false,
          "spoiler": false,
          "locked": false,
          "author_flair_text": null,
          "treatment_tags": [],
          "visited": false,
          "removed_by": null,
          "num_reports": null,
          "distinguished": null,
          "subreddit_id": "t5_2qh36",
          "mod_reason_by": null,
          "removal_reason": null,
          "link_flair_background_color": "",
          "id": "glz389",
          "is_robot_indexable": true,
          "report_reasons": null,
          "author": "pavelpotocek",
          "discussion_type": null,
          "num_comments": 175,
          "send_replies": true,
          "whitelist_status": "all_ads",
          "contest_mode": false,
          "mod_reports": [],
          "author_patreon_flair": false,
          "author_flair_text_color": null,
          "permalink": "/r/haskell/comments/glz389/examples_of_incorrect_abstractions_in_other/",
          "parent_whitelist_status": "all_ads",
          "stickied": false,
          "url": "https://old.reddit.com/r/haskell/comments/glz389/examples_of_incorrect_abstractions_in_other/",
          "subreddit_subscribers": 55194,
          "created_utc": 1589798248,
          "num_crossposts": 0,
          "media": null,
          "is_video": false
        }
      },
      {
        "kind": "t3",
        "data": {
          "approved_at_utc": null,
          "subreddit": "haskell",
          "selftext": "",
          "author_fullname": "t2_2o6ongui",
          "saved": false,
          "mod_reason_title": null,
          "gilded": 0,
          "clicked": false,
          "title": "[ANN] Medea - a json schema language",
          "link_flair_richtext": [],
          "subreddit_name_prefixed": "r/haskell",
          "hidden": false,
          "pwls": 6,
          "link_flair_css_class": null,
          "downs": 0,
          "hide_score": false,
          "name": "t3_gma3p4",
          "quarantine": false,
          "link_flair_text_color": "dark",
          "upvote_ratio": 0.93,
          "author_flair_background_color": null,
          "subreddit_type": "public",
          "ups": 11,
          "total_awards_received": 0,
          "media_embed": {},
          "author_flair_template_id": null,
          "is_original_content": false,
          "user_reports": [],
          "secure_media": null,
          "is_reddit_media_domain": false,
          "is_meta": false,
          "category": null,
          "secure_media_embed": {},
          "link_flair_text": null,
          "can_mod_post": false,
          "score": 11,
          "approved_by": null,
          "author_premium": false,
          "thumbnail": "",
          "edited": false,
          "author_flair_css_class": null,
          "author_flair_richtext": [],
          "gildings": {},
          "content_categories": null,
          "is_self": false,
          "mod_note": null,
          "created": 1589864384,
          "link_flair_type": "text",
          "wls": 6,
          "removed_by_category": null,
          "banned_by": null,
          "author_flair_type": "text",
          "domain": "github.com",
          "allow_live_comments": false,
          "selftext_html": null,
          "likes": null,
          "suggested_sort": null,
          "banned_at_utc": null,
          "view_count": null,
          "archived": false,
          "no_follow": false,
          "is_crosspostable": false,
          "pinned": false,
          "over_18": false,
          "all_awardings": [],
          "awarders": [],
          "media_only": false,
          "can_gild": false,
          "spoiler": false,
          "locked": false,
          "author_flair_text": null,
          "treatment_tags": [],
          "visited": false,
          "removed_by": null,
          "num_reports": null,
          "distinguished": null,
          "subreddit_id": "t5_2qh36",
          "mod_reason_by": null,
          "removal_reason": null,
          "link_flair_background_color": "",
          "id": "gma3p4",
          "is_robot_indexable": true,
          "report_reasons": null,
          "author": "restarted_mustard",
          "discussion_type": null,
          "num_comments": 2,
          "send_replies": true,
          "whitelist_status": "all_ads",
          "contest_mode": false,
          "mod_reports": [],
          "author_patreon_flair": false,
          "author_flair_text_color": null,
          "permalink": "/r/haskell/comments/gma3p4/ann_medea_a_json_schema_language/",
          "parent_whitelist_status": "all_ads",
          "stickied": false,
          "url": "https://github.com/juspay/medea",
          "subreddit_subscribers": 55194,
          "created_utc": 1589835584,
          "num_crossposts": 0,
          "media": null,
          "is_video": false
        }
      },
      {
        "kind": "t3",
        "data": {
          "approved_at_utc": null,
          "subreddit": "haskell",
          "selftext": "There seem to be some [posts](https://www.reddit.com/r/haskell/comments/pen8s/anyone_else_used_write_yourself_a_scheme_in_48/) about the book or the [Write You a Scheme V2.0](https://wespiser.com/writings/wyas/00_overview.html), but I'm unsure how much Scheme I need to tackle this project.\n\nI've thumbed through the (in)famous Learn You a Haskell, and implementing an interpreter sounds like a lot of fun, but perhaps I might not down this path if I have to spend the time to buckle down and learn some Scheme syntax too.",
          "author_fullname": "t2_5y26z8w2",
          "saved": false,
          "mod_reason_title": null,
          "gilded": 0,
          "clicked": false,
          "title": "How much Scheme needed for \"Write yourself a Scheme in 48 hours?\"",
          "link_flair_richtext": [],
          "subreddit_name_prefixed": "r/haskell",
          "hidden": false,
          "pwls": 6,
          "link_flair_css_class": null,
          "downs": 0,
          "hide_score": false,
          "name": "t3_gm3ia1",
          "quarantine": false,
          "link_flair_text_color": "dark",
          "upvote_ratio": 0.97,
          "author_flair_background_color": null,
          "subreddit_type": "public",
          "ups": 21,
          "total_awards_received": 0,
          "media_embed": {},
          "author_flair_template_id": null,
          "is_original_content": false,
          "user_reports": [],
          "secure_media": null,
          "is_reddit_media_domain": false,
          "is_meta": false,
          "category": null,
          "secure_media_embed": {},
          "link_flair_text": null,
          "can_mod_post": false,
          "score": 21,
          "approved_by": null,
          "author_premium": false,
          "thumbnail": "",
          "edited": false,
          "author_flair_css_class": null,
          "author_flair_richtext": [],
          "gildings": {},
          "content_categories": null,
          "is_self": true,
          "mod_note": null,
          "created": 1589844357,
          "link_flair_type": "text",
          "wls": 6,
          "removed_by_category": null,
          "banned_by": null,
          "author_flair_type": "text",
          "domain": "self.haskell",
          "allow_live_comments": false,
          "selftext_html": "&lt;!-- SC_OFF --&gt;&lt;div class=\"md\"&gt;&lt;p&gt;There seem to be some &lt;a href=\"https://www.reddit.com/r/haskell/comments/pen8s/anyone_else_used_write_yourself_a_scheme_in_48/\"&gt;posts&lt;/a&gt; about the book or the &lt;a href=\"https://wespiser.com/writings/wyas/00_overview.html\"&gt;Write You a Scheme V2.0&lt;/a&gt;, but I&amp;#39;m unsure how much Scheme I need to tackle this project.&lt;/p&gt;\n\n&lt;p&gt;I&amp;#39;ve thumbed through the (in)famous Learn You a Haskell, and implementing an interpreter sounds like a lot of fun, but perhaps I might not down this path if I have to spend the time to buckle down and learn some Scheme syntax too.&lt;/p&gt;\n&lt;/div&gt;&lt;!-- SC_ON --&gt;",
          "likes": null,
          "suggested_sort": null,
          "banned_at_utc": null,
          "view_count": null,
          "archived": false,
          "no_follow": false,
          "is_crosspostable": false,
          "pinned": false,
          "over_18": false,
          "all_awardings": [],
          "awarders": [],
          "media_only": false,
          "can_gild": false,
          "spoiler": false,
          "locked": false,
          "author_flair_text": null,
          "treatment_tags": [],
          "visited": false,
          "removed_by": null,
          "num_reports": null,
          "distinguished": null,
          "subreddit_id": "t5_2qh36",
          "mod_reason_by": null,
          "removal_reason": null,
          "link_flair_background_color": "",
          "id": "gm3ia1",
          "is_robot_indexable": true,
          "report_reasons": null,
          "author": "0x2fwhc",
          "discussion_type": null,
          "num_comments": 5,
          "send_replies": false,
          "whitelist_status": "all_ads",
          "contest_mode": false,
          "mod_reports": [],
          "author_patreon_flair": false,
          "author_flair_text_color": null,
          "permalink": "/r/haskell/comments/gm3ia1/how_much_scheme_needed_for_write_yourself_a/",
          "parent_whitelist_status": "all_ads",
          "stickied": false,
          "url": "https://old.reddit.com/r/haskell/comments/gm3ia1/how_much_scheme_needed_for_write_yourself_a/",
          "subreddit_subscribers": 55194,
          "created_utc": 1589815557,
          "num_crossposts": 0,
          "media": null,
          "is_video": false
        }
      },
      {
        "kind": "t3",
        "data": {
          "approved_at_utc": null,
          "subreddit": "haskell",
          "selftext": "GHC has releases versions 8.4.x, and 8.6.x, but there are no 8.5.x releases. Why does GHC skip odd minor versions?",
          "author_fullname": "t2_2lv4dufx",
          "saved": false,
          "mod_reason_title": null,
          "gilded": 0,
          "clicked": false,
          "title": "GHC versioning scheme",
          "link_flair_richtext": [],
          "subreddit_name_prefixed": "r/haskell",
          "hidden": false,
          "pwls": 6,
          "link_flair_css_class": null,
          "downs": 0,
          "hide_score": false,
          "name": "t3_gm6mm7",
          "quarantine": false,
          "link_flair_text_color": "dark",
          "upvote_ratio": 1,
          "author_flair_background_color": null,
          "subreddit_type": "public",
          "ups": 9,
          "total_awards_received": 0,
          "media_embed": {},
          "author_flair_template_id": null,
          "is_original_content": false,
          "user_reports": [],
          "secure_media": null,
          "is_reddit_media_domain": false,
          "is_meta": false,
          "category": null,
          "secure_media_embed": {},
          "link_flair_text": null,
          "can_mod_post": false,
          "score": 9,
          "approved_by": null,
          "author_premium": false,
          "thumbnail": "",
          "edited": false,
          "author_flair_css_class": null,
          "author_flair_richtext": [],
          "gildings": {},
          "content_categories": null,
          "is_self": true,
          "mod_note": null,
          "created": 1589853843,
          "link_flair_type": "text",
          "wls": 6,
          "removed_by_category": null,
          "banned_by": null,
          "author_flair_type": "text",
          "domain": "self.haskell",
          "allow_live_comments": false,
          "selftext_html": "&lt;!-- SC_OFF --&gt;&lt;div class=\"md\"&gt;&lt;p&gt;GHC has releases versions 8.4.x, and 8.6.x, but there are no 8.5.x releases. Why does GHC skip odd minor versions?&lt;/p&gt;\n&lt;/div&gt;&lt;!-- SC_ON --&gt;",
          "likes": null,
          "suggested_sort": null,
          "banned_at_utc": null,
          "view_count": null,
          "archived": false,
          "no_follow": false,
          "is_crosspostable": false,
          "pinned": false,
          "over_18": false,
          "all_awardings": [],
          "awarders": [],
          "media_only": false,
          "can_gild": false,
          "spoiler": false,
          "locked": false,
          "author_flair_text": null,
          "treatment_tags": [],
          "visited": false,
          "removed_by": null,
          "num_reports": null,
          "distinguished": null,
          "subreddit_id": "t5_2qh36",
          "mod_reason_by": null,
          "removal_reason": null,
          "link_flair_background_color": "",
          "id": "gm6mm7",
          "is_robot_indexable": true,
          "report_reasons": null,
          "author": "NinjaPenguin54",
          "discussion_type": null,
          "num_comments": 6,
          "send_replies": true,
          "whitelist_status": "all_ads",
          "contest_mode": false,
          "mod_reports": [],
          "author_patreon_flair": false,
          "author_flair_text_color": null,
          "permalink": "/r/haskell/comments/gm6mm7/ghc_versioning_scheme/",
          "parent_whitelist_status": "all_ads",
          "stickied": false,
          "url": "https://old.reddit.com/r/haskell/comments/gm6mm7/ghc_versioning_scheme/",
          "subreddit_subscribers": 55194,
          "created_utc": 1589825043,
          "num_crossposts": 0,
          "media": null,
          "is_video": false
        }
      },
      {
        "kind": "t3",
        "data": {
          "approved_at_utc": null,
          "subreddit": "haskell",
          "selftext": "Hello fellow Haskellers,\n\nI've spent last half year learning Haskell and managed to write my first real-world Haskell application. Now I have some ideas for Haskell libraries, that could be (hopefully) useful, but have zero experience designing library for Haskell (mainly from API perspective). Building library is clearly different than building CLI tool, as the main \"API\" of CLI tool is the command line interface, which is pretty restrictive, but library API should be more flexible to suit different styles and designs of end-user programs. Also if such library is badly designed from start, it's hard to completely change the API style as it breaks compatibility and causes troubles. So I'd like to ask you to share your experience on this topic, mainly following points:\n\n1. **handling exceptions** \\- I know, this is probably controversial topic, but I'd like to know whether there is any current consensus. Let's say that my library will provide IO operations that may fail because 1/ there is no result for the given input or 2/ there is some IO error (file doesn't exist, etc.). In my CLI tool, I used the approach summarized by u/snoyberg in [this blog post](https://www.fpcomplete.com/blog/2016/11/exceptions-best-practices-haskell), i.e. using `MonadThrow` with `MonadIO`, like `parseJsonFile :: (MonadThrow m, MonadIO m) =&gt; FilePath -&gt; m JSON`. But I'm wondering if this is good approach for library? Because the `MonadThrow` itself isn't really specific about the type of the error it can throw. Would it be better to use something as `MonadError` maybe?\n2. **RIO** \\- In my CLI app I'm pretty happy with [RIO](https://hackage.haskell.org/package/rio), both as Prelude replacement and RIO Monad, but I guess it's not good idea to force end-users to use the RIO-style in library, right?\n3. **language extensions** \\- GHC language extensions are pretty common to use nowadays, but are there any of them I should explicitly avoid using in libraries?\n4. **overall architecture** \\- This is closely related to 1). Should I go full mtl for the library design, or maybe keep it simpler and use just some combination of things like `MonadIO`, `MonadThrow` or `MonadError`?\n\nI'll be grateful for any shared experience, comments, links to blog posts/book. Thanks a lot in advance.",
          "author_fullname": "t2_kjucw",
          "saved": false,
          "mod_reason_title": null,
          "gilded": 0,
          "clicked": false,
          "title": "Designing Haskell library - best practices?",
          "link_flair_richtext": [],
          "subreddit_name_prefixed": "r/haskell",
          "hidden": false,
          "pwls": 6,
          "link_flair_css_class": null,
          "downs": 0,
          "hide_score": false,
          "name": "t3_gm3v3g",
          "quarantine": false,
          "link_flair_text_color": "dark",
          "upvote_ratio": 0.85,
          "author_flair_background_color": null,
          "subreddit_type": "public",
          "ups": 9,
          "total_awards_received": 0,
          "media_embed": {},
          "author_flair_template_id": null,
          "is_original_content": false,
          "user_reports": [],
          "secure_media": null,
          "is_reddit_media_domain": false,
          "is_meta": false,
          "category": null,
          "secure_media_embed": {},
          "link_flair_text": null,
          "can_mod_post": false,
          "score": 9,
          "approved_by": null,
          "author_premium": false,
          "thumbnail": "",
          "edited": false,
          "author_flair_css_class": null,
          "author_flair_richtext": [],
          "gildings": {},
          "content_categories": null,
          "is_self": true,
          "mod_note": null,
          "created": 1589845467,
          "link_flair_type": "text",
          "wls": 6,
          "removed_by_category": null,
          "banned_by": null,
          "author_flair_type": "text",
          "domain": "self.haskell",
          "allow_live_comments": false,
          "selftext_html": "&lt;!-- SC_OFF --&gt;&lt;div class=\"md\"&gt;&lt;p&gt;Hello fellow Haskellers,&lt;/p&gt;\n\n&lt;p&gt;I&amp;#39;ve spent last half year learning Haskell and managed to write my first real-world Haskell application. Now I have some ideas for Haskell libraries, that could be (hopefully) useful, but have zero experience designing library for Haskell (mainly from API perspective). Building library is clearly different than building CLI tool, as the main &amp;quot;API&amp;quot; of CLI tool is the command line interface, which is pretty restrictive, but library API should be more flexible to suit different styles and designs of end-user programs. Also if such library is badly designed from start, it&amp;#39;s hard to completely change the API style as it breaks compatibility and causes troubles. So I&amp;#39;d like to ask you to share your experience on this topic, mainly following points:&lt;/p&gt;\n\n&lt;ol&gt;\n&lt;li&gt;&lt;strong&gt;handling exceptions&lt;/strong&gt; - I know, this is probably controversial topic, but I&amp;#39;d like to know whether there is any current consensus. Let&amp;#39;s say that my library will provide IO operations that may fail because 1/ there is no result for the given input or 2/ there is some IO error (file doesn&amp;#39;t exist, etc.). In my CLI tool, I used the approach summarized by &lt;a href=\"/u/snoyberg\"&gt;u/snoyberg&lt;/a&gt; in &lt;a href=\"https://www.fpcomplete.com/blog/2016/11/exceptions-best-practices-haskell\"&gt;this blog post&lt;/a&gt;, i.e. using &lt;code&gt;MonadThrow&lt;/code&gt; with &lt;code&gt;MonadIO&lt;/code&gt;, like &lt;code&gt;parseJsonFile :: (MonadThrow m, MonadIO m) =&amp;gt; FilePath -&amp;gt; m JSON&lt;/code&gt;. But I&amp;#39;m wondering if this is good approach for library? Because the &lt;code&gt;MonadThrow&lt;/code&gt; itself isn&amp;#39;t really specific about the type of the error it can throw. Would it be better to use something as &lt;code&gt;MonadError&lt;/code&gt; maybe?&lt;/li&gt;\n&lt;li&gt;&lt;strong&gt;RIO&lt;/strong&gt; - In my CLI app I&amp;#39;m pretty happy with &lt;a href=\"https://hackage.haskell.org/package/rio\"&gt;RIO&lt;/a&gt;, both as Prelude replacement and RIO Monad, but I guess it&amp;#39;s not good idea to force end-users to use the RIO-style in library, right?&lt;/li&gt;\n&lt;li&gt;&lt;strong&gt;language extensions&lt;/strong&gt; - GHC language extensions are pretty common to use nowadays, but are there any of them I should explicitly avoid using in libraries?&lt;/li&gt;\n&lt;li&gt;&lt;strong&gt;overall architecture&lt;/strong&gt; - This is closely related to 1). Should I go full mtl for the library design, or maybe keep it simpler and use just some combination of things like &lt;code&gt;MonadIO&lt;/code&gt;, &lt;code&gt;MonadThrow&lt;/code&gt; or &lt;code&gt;MonadError&lt;/code&gt;?&lt;/li&gt;\n&lt;/ol&gt;\n\n&lt;p&gt;I&amp;#39;ll be grateful for any shared experience, comments, links to blog posts/book. Thanks a lot in advance.&lt;/p&gt;\n&lt;/div&gt;&lt;!-- SC_ON --&gt;",
          "likes": null,
          "suggested_sort": null,
          "banned_at_utc": null,
          "view_count": null,
          "archived": false,
          "no_follow": false,
          "is_crosspostable": false,
          "pinned": false,
          "over_18": false,
          "all_awardings": [],
          "awarders": [],
          "media_only": false,
          "can_gild": false,
          "spoiler": false,
          "locked": false,
          "author_flair_text": null,
          "treatment_tags": [],
          "visited": false,
          "removed_by": null,
          "num_reports": null,
          "distinguished": null,
          "subreddit_id": "t5_2qh36",
          "mod_reason_by": null,
          "removal_reason": null,
          "link_flair_background_color": "",
          "id": "gm3v3g",
          "is_robot_indexable": true,
          "report_reasons": null,
          "author": "xwinus",
          "discussion_type": null,
          "num_comments": 5,
          "send_replies": true,
          "whitelist_status": "all_ads",
          "contest_mode": false,
          "mod_reports": [],
          "author_patreon_flair": false,
          "author_flair_text_color": null,
          "permalink": "/r/haskell/comments/gm3v3g/designing_haskell_library_best_practices/",
          "parent_whitelist_status": "all_ads",
          "stickied": false,
          "url": "https://old.reddit.com/r/haskell/comments/gm3v3g/designing_haskell_library_best_practices/",
          "subreddit_subscribers": 55194,
          "created_utc": 1589816667,
          "num_crossposts": 0,
          "media": null,
          "is_video": false
        }
      },
      {
        "kind": "t3",
        "data": {
          "approved_at_utc": null,
          "subreddit": "haskell",
          "selftext": "Un dictionnaire en Python peut contenir des données de toute sortes de type.\n\nDans ce nouveau chapitre, nous allons utiliser le système de type pour créer des enregistrements « extensibles », ce qui revient à appliquer des règles de typage aux objets ad hoc des langages dynamiques.\n\nC'est un bon prétexte pour faire un retour sur plusieurs notions déjà abordées : les représentations canoniques, les Types Somme, Produit, existentiels, de rang n et les types de donnée algébriques généralisés.\n\nEn s'exerçant à leur usage, nous verrons aussi de nouvelles notions et pratiques, comme :\n\n* les types indexés,\n* les tandems de constructeurs de donnée dangereux rendus sûr par des constructeurs intelligents,\n* des éléments du module GHC.TypeLits et du paquet first-class-families,\n* se servir de familles de types comme contrainte ou index sur un type Produit,\n* les étiquettes surchargées (extension OverloadedLabels) qui permettent de transformer `get (Key @\"example\") foo` en `get #example foo` (c'est aussi l'occasion de parler d'astuce de contrainte et d'en-tête d’instance).\n\nFaîtes circuler l'info s'il vous plaît, ça me rend bien service.\n\nBonne réflexion !",
          "author_fullname": "t2_167bmq",
          "saved": false,
          "mod_reason_title": null,
          "gilded": 0,
          "clicked": false,
          "title": "\"Penser en Types\" - Chapitre 11 (update in the translation of \"Thinking with Types\")",
          "link_flair_richtext": [],
          "subreddit_name_prefixed": "r/haskell",
          "hidden": false,
          "pwls": 6,
          "link_flair_css_class": null,
          "downs": 0,
          "hide_score": false,
          "name": "t3_gm5nzd",
          "quarantine": false,
          "link_flair_text_color": "dark",
          "upvote_ratio": 0.67,
          "author_flair_background_color": null,
          "subreddit_type": "public",
          "ups": 4,
          "total_awards_received": 0,
          "media_embed": {},
          "author_flair_template_id": null,
          "is_original_content": false,
          "user_reports": [],
          "secure_media": null,
          "is_reddit_media_domain": false,
          "is_meta": false,
          "category": null,
          "secure_media_embed": {},
          "link_flair_text": null,
          "can_mod_post": false,
          "score": 4,
          "approved_by": null,
          "author_premium": false,
          "thumbnail": "",
          "edited": false,
          "author_flair_css_class": null,
          "author_flair_richtext": [],
          "gildings": {},
          "content_categories": null,
          "is_self": true,
          "mod_note": null,
          "created": 1589850981,
          "link_flair_type": "text",
          "wls": 6,
          "removed_by_category": null,
          "banned_by": null,
          "author_flair_type": "text",
          "domain": "self.haskell",
          "allow_live_comments": false,
          "selftext_html": "&lt;!-- SC_OFF --&gt;&lt;div class=\"md\"&gt;&lt;p&gt;Un dictionnaire en Python peut contenir des données de toute sortes de type.&lt;/p&gt;\n\n&lt;p&gt;Dans ce nouveau chapitre, nous allons utiliser le système de type pour créer des enregistrements « extensibles », ce qui revient à appliquer des règles de typage aux objets ad hoc des langages dynamiques.&lt;/p&gt;\n\n&lt;p&gt;C&amp;#39;est un bon prétexte pour faire un retour sur plusieurs notions déjà abordées : les représentations canoniques, les Types Somme, Produit, existentiels, de rang n et les types de donnée algébriques généralisés.&lt;/p&gt;\n\n&lt;p&gt;En s&amp;#39;exerçant à leur usage, nous verrons aussi de nouvelles notions et pratiques, comme :&lt;/p&gt;\n\n&lt;ul&gt;\n&lt;li&gt;les types indexés,&lt;/li&gt;\n&lt;li&gt;les tandems de constructeurs de donnée dangereux rendus sûr par des constructeurs intelligents,&lt;/li&gt;\n&lt;li&gt;des éléments du module GHC.TypeLits et du paquet first-class-families,&lt;/li&gt;\n&lt;li&gt;se servir de familles de types comme contrainte ou index sur un type Produit,&lt;/li&gt;\n&lt;li&gt;les étiquettes surchargées (extension OverloadedLabels) qui permettent de transformer &lt;code&gt;get (Key @&amp;quot;example&amp;quot;) foo&lt;/code&gt; en &lt;code&gt;get #example foo&lt;/code&gt; (c&amp;#39;est aussi l&amp;#39;occasion de parler d&amp;#39;astuce de contrainte et d&amp;#39;en-tête d’instance).&lt;/li&gt;\n&lt;/ul&gt;\n\n&lt;p&gt;Faîtes circuler l&amp;#39;info s&amp;#39;il vous plaît, ça me rend bien service.&lt;/p&gt;\n\n&lt;p&gt;Bonne réflexion !&lt;/p&gt;\n&lt;/div&gt;&lt;!-- SC_ON --&gt;",
          "likes": null,
          "suggested_sort": null,
          "banned_at_utc": null,
          "view_count": null,
          "archived": false,
          "no_follow": false,
          "is_crosspostable": false,
          "pinned": false,
          "over_18": false,
          "all_awardings": [],
          "awarders": [],
          "media_only": false,
          "can_gild": false,
          "spoiler": false,
          "locked": false,
          "author_flair_text": null,
          "treatment_tags": [],
          "visited": false,
          "removed_by": null,
          "num_reports": null,
          "distinguished": null,
          "subreddit_id": "t5_2qh36",
          "mod_reason_by": null,
          "removal_reason": null,
          "link_flair_background_color": "",
          "id": "gm5nzd",
          "is_robot_indexable": true,
          "report_reasons": null,
          "author": "jhderaigniac",
          "discussion_type": null,
          "num_comments": 0,
          "send_replies": true,
          "whitelist_status": "all_ads",
          "contest_mode": false,
          "mod_reports": [],
          "author_patreon_flair": false,
          "author_flair_text_color": null,
          "permalink": "/r/haskell/comments/gm5nzd/penser_en_types_chapitre_11_update_in_the/",
          "parent_whitelist_status": "all_ads",
          "stickied": false,
          "url": "https://old.reddit.com/r/haskell/comments/gm5nzd/penser_en_types_chapitre_11_update_in_the/",
          "subreddit_subscribers": 55194,
          "created_utc": 1589822181,
          "num_crossposts": 0,
          "media": null,
          "is_video": false
        }
      },
      {
        "kind": "t3",
        "data": {
          "approved_at_utc": null,
          "subreddit": "haskell",
          "selftext": "Hello,\n\nI could not find the answer anywhere so I thought I might ask here. My package was included in Stackage sometime at the end of April, but it's still not in any LTS release even though there have been a couple of LTS version bumps since then. What is the policy here? Is there anything I should do? Thanks in advance",
          "author_fullname": "t2_3epm",
          "saved": false,
          "mod_reason_title": null,
          "gilded": 0,
          "clicked": false,
          "title": "When packages are promoted to LTS in Stackage?",
          "link_flair_richtext": [],
          "subreddit_name_prefixed": "r/haskell",
          "hidden": false,
          "pwls": 6,
          "link_flair_css_class": null,
          "downs": 0,
          "hide_score": false,
          "name": "t3_gm2484",
          "quarantine": false,
          "link_flair_text_color": "dark",
          "upvote_ratio": 1,
          "author_flair_background_color": null,
          "subreddit_type": "public",
          "ups": 7,
          "total_awards_received": 0,
          "media_embed": {},
          "author_flair_template_id": null,
          "is_original_content": false,
          "user_reports": [],
          "secure_media": null,
          "is_reddit_media_domain": false,
          "is_meta": false,
          "category": null,
          "secure_media_embed": {},
          "link_flair_text": null,
          "can_mod_post": false,
          "score": 7,
          "approved_by": null,
          "author_premium": false,
          "thumbnail": "",
          "edited": false,
          "author_flair_css_class": null,
          "author_flair_richtext": [],
          "gildings": {},
          "content_categories": null,
          "is_self": true,
          "mod_note": null,
          "created": 1589839723,
          "link_flair_type": "text",
          "wls": 6,
          "removed_by_category": null,
          "banned_by": null,
          "author_flair_type": "text",
          "domain": "self.haskell",
          "allow_live_comments": false,
          "selftext_html": "&lt;!-- SC_OFF --&gt;&lt;div class=\"md\"&gt;&lt;p&gt;Hello,&lt;/p&gt;\n\n&lt;p&gt;I could not find the answer anywhere so I thought I might ask here. My package was included in Stackage sometime at the end of April, but it&amp;#39;s still not in any LTS release even though there have been a couple of LTS version bumps since then. What is the policy here? Is there anything I should do? Thanks in advance&lt;/p&gt;\n&lt;/div&gt;&lt;!-- SC_ON --&gt;",
          "likes": null,
          "suggested_sort": null,
          "banned_at_utc": null,
          "view_count": null,
          "archived": false,
          "no_follow": false,
          "is_crosspostable": false,
          "pinned": false,
          "over_18": false,
          "all_awardings": [],
          "awarders": [],
          "media_only": false,
          "can_gild": false,
          "spoiler": false,
          "locked": false,
          "author_flair_text": null,
          "treatment_tags": [],
          "visited": false,
          "removed_by": null,
          "num_reports": null,
          "distinguished": null,
          "subreddit_id": "t5_2qh36",
          "mod_reason_by": null,
          "removal_reason": null,
          "link_flair_background_color": "",
          "id": "gm2484",
          "is_robot_indexable": true,
          "report_reasons": null,
          "author": "rzeznik",
          "discussion_type": null,
          "num_comments": 2,
          "send_replies": true,
          "whitelist_status": "all_ads",
          "contest_mode": false,
          "mod_reports": [],
          "author_patreon_flair": false,
          "author_flair_text_color": null,
          "permalink": "/r/haskell/comments/gm2484/when_packages_are_promoted_to_lts_in_stackage/",
          "parent_whitelist_status": "all_ads",
          "stickied": false,
          "url": "https://old.reddit.com/r/haskell/comments/gm2484/when_packages_are_promoted_to_lts_in_stackage/",
          "subreddit_subscribers": 55194,
          "created_utc": 1589810923,
          "num_crossposts": 0,
          "media": null,
          "is_video": false
        }
      },
      {
        "kind": "t3",
        "data": {
          "approved_at_utc": null,
          "subreddit": "haskell",
          "selftext": "",
          "author_fullname": "t2_o5q8o",
          "saved": false,
          "mod_reason_title": null,
          "gilded": 0,
          "clicked": false,
          "title": "[ANN] password-2.0: library for working with passwords and password hashes",
          "link_flair_richtext": [],
          "subreddit_name_prefixed": "r/haskell",
          "hidden": false,
          "pwls": 6,
          "link_flair_css_class": null,
          "downs": 0,
          "hide_score": false,
          "name": "t3_glte2r",
          "quarantine": false,
          "link_flair_text_color": "dark",
          "upvote_ratio": 0.93,
          "author_flair_background_color": null,
          "subreddit_type": "public",
          "ups": 45,
          "total_awards_received": 0,
          "media_embed": {},
          "author_flair_template_id": null,
          "is_original_content": false,
          "user_reports": [],
          "secure_media": null,
          "is_reddit_media_domain": false,
          "is_meta": false,
          "category": null,
          "secure_media_embed": {},
          "link_flair_text": null,
          "can_mod_post": false,
          "score": 45,
          "approved_by": null,
          "author_premium": false,
          "thumbnail": "",
          "edited": false,
          "author_flair_css_class": null,
          "author_flair_richtext": [],
          "gildings": {},
          "content_categories": null,
          "is_self": false,
          "mod_note": null,
          "created": 1589800022,
          "link_flair_type": "text",
          "wls": 6,
          "removed_by_category": null,
          "banned_by": null,
          "author_flair_type": "text",
          "domain": "functor.tokyo",
          "allow_live_comments": false,
          "selftext_html": null,
          "likes": null,
          "suggested_sort": null,
          "banned_at_utc": null,
          "view_count": null,
          "archived": false,
          "no_follow": false,
          "is_crosspostable": false,
          "pinned": false,
          "over_18": false,
          "all_awardings": [],
          "awarders": [],
          "media_only": false,
          "can_gild": false,
          "spoiler": false,
          "locked": false,
          "author_flair_text": null,
          "treatment_tags": [],
          "visited": false,
          "removed_by": null,
          "num_reports": null,
          "distinguished": null,
          "subreddit_id": "t5_2qh36",
          "mod_reason_by": null,
          "removal_reason": null,
          "link_flair_background_color": "",
          "id": "glte2r",
          "is_robot_indexable": true,
          "report_reasons": null,
          "author": "cdep_illabout",
          "discussion_type": null,
          "num_comments": 0,
          "send_replies": true,
          "whitelist_status": "all_ads",
          "contest_mode": false,
          "mod_reports": [],
          "author_patreon_flair": false,
          "author_flair_text_color": null,
          "permalink": "/r/haskell/comments/glte2r/ann_password20_library_for_working_with_passwords/",
          "parent_whitelist_status": "all_ads",
          "stickied": false,
          "url": "https://functor.tokyo/blog/2020-05-18-password-2.0",
          "subreddit_subscribers": 55194,
          "created_utc": 1589771222,
          "num_crossposts": 0,
          "media": null,
          "is_video": false
        }
      },
      {
        "kind": "t3",
        "data": {
          "approved_at_utc": null,
          "subreddit": "haskell",
          "selftext": "",
          "author_fullname": "t2_137hg4",
          "saved": false,
          "mod_reason_title": null,
          "gilded": 0,
          "clicked": false,
          "title": "Trade-Offs in Type Safety",
          "link_flair_richtext": [],
          "subreddit_name_prefixed": "r/haskell",
          "hidden": false,
          "pwls": 6,
          "link_flair_css_class": null,
          "downs": 0,
          "hide_score": false,
          "name": "t3_glzz0l",
          "quarantine": false,
          "link_flair_text_color": "dark",
          "upvote_ratio": 0.69,
          "author_flair_background_color": null,
          "subreddit_type": "public",
          "ups": 8,
          "total_awards_received": 0,
          "media_embed": {},
          "author_flair_template_id": null,
          "is_original_content": false,
          "user_reports": [],
          "secure_media": null,
          "is_reddit_media_domain": false,
          "is_meta": false,
          "category": null,
          "secure_media_embed": {},
          "link_flair_text": null,
          "can_mod_post": false,
          "score": 8,
          "approved_by": null,
          "author_premium": false,
          "thumbnail": "",
          "edited": false,
          "author_flair_css_class": null,
          "author_flair_richtext": [],
          "gildings": {},
          "content_categories": null,
          "is_self": false,
          "mod_note": null,
          "created": 1589831325,
          "link_flair_type": "text",
          "wls": 6,
          "removed_by_category": null,
          "banned_by": null,
          "author_flair_type": "text",
          "domain": "alpacaaa.net",
          "allow_live_comments": false,
          "selftext_html": null,
          "likes": null,
          "suggested_sort": null,
          "banned_at_utc": null,
          "view_count": null,
          "archived": false,
          "no_follow": false,
          "is_crosspostable": false,
          "pinned": false,
          "over_18": false,
          "all_awardings": [],
          "awarders": [],
          "media_only": false,
          "can_gild": false,
          "spoiler": false,
          "locked": false,
          "author_flair_text": null,
          "treatment_tags": [],
          "visited": false,
          "removed_by": null,
          "num_reports": null,
          "distinguished": null,
          "subreddit_id": "t5_2qh36",
          "mod_reason_by": null,
          "removal_reason": null,
          "link_flair_background_color": "",
          "id": "glzz0l",
          "is_robot_indexable": true,
          "report_reasons": null,
          "author": "_alpacaaa",
          "discussion_type": null,
          "num_comments": 27,
          "send_replies": true,
          "whitelist_status": "all_ads",
          "contest_mode": false,
          "mod_reports": [],
          "author_patreon_flair": false,
          "author_flair_text_color": null,
          "permalink": "/r/haskell/comments/glzz0l/tradeoffs_in_type_safety/",
          "parent_whitelist_status": "all_ads",
          "stickied": false,
          "url": "https://alpacaaa.net/type-safety/",
          "subreddit_subscribers": 55194,
          "created_utc": 1589802525,
          "num_crossposts": 0,
          "media": null,
          "is_video": false
        }
      },
      {
        "kind": "t3",
        "data": {
          "approved_at_utc": null,
          "subreddit": "haskell",
          "selftext": "The Chalmers Online Functional Programming Seminar Series is organized by the Chalmers Functional Programming Group, as a way to exploit the fact that so many of us in the FP community are already meeting and working online these days. Our aim is to bring the people in the FP community closer together, to educate and inspire, and to foster collaboration.\n\nThe seminars will take place every Monday (at 7am PDT / 10am EDT / 16:00 CEST) and are **live streamed through YouTube**, and questions are taken through **sli.do**.\n\nWe continue tomorrow with Benjamin Pierce; title \"Backtracking Generators for Random Testing\". All welcome!\n\nLink to program, including videos of previous talks:\n\nhttp://chalmersfp.org/",
          "author_fullname": "t2_9ork9",
          "saved": false,
          "mod_reason_title": null,
          "gilded": 0,
          "clicked": false,
          "title": "Reminder: The Chalmers Online Functional Programming Seminar Series continues tomorrow (Monday) with a talk by Benjamin Pierce",
          "link_flair_richtext": [],
          "subreddit_name_prefixed": "r/haskell",
          "hidden": false,
          "pwls": 6,
          "link_flair_css_class": null,
          "downs": 0,
          "hide_score": false,
          "name": "t3_gld45o",
          "quarantine": false,
          "link_flair_text_color": "dark",
          "upvote_ratio": 0.98,
          "author_flair_background_color": null,
          "subreddit_type": "public",
          "ups": 89,
          "total_awards_received": 0,
          "media_embed": {},
          "author_flair_template_id": null,
          "is_original_content": false,
          "user_reports": [],
          "secure_media": null,
          "is_reddit_media_domain": false,
          "is_meta": false,
          "category": null,
          "secure_media_embed": {},
          "link_flair_text": null,
          "can_mod_post": false,
          "score": 89,
          "approved_by": null,
          "author_premium": false,
          "thumbnail": "",
          "edited": 1589711120,
          "author_flair_css_class": null,
          "author_flair_richtext": [],
          "gildings": {},
          "content_categories": null,
          "is_self": true,
          "mod_note": null,
          "created": 1589739615,
          "link_flair_type": "text",
          "wls": 6,
          "removed_by_category": null,
          "banned_by": null,
          "author_flair_type": "text",
          "domain": "self.haskell",
          "allow_live_comments": false,
          "selftext_html": "&lt;!-- SC_OFF --&gt;&lt;div class=\"md\"&gt;&lt;p&gt;The Chalmers Online Functional Programming Seminar Series is organized by the Chalmers Functional Programming Group, as a way to exploit the fact that so many of us in the FP community are already meeting and working online these days. Our aim is to bring the people in the FP community closer together, to educate and inspire, and to foster collaboration.&lt;/p&gt;\n\n&lt;p&gt;The seminars will take place every Monday (at 7am PDT / 10am EDT / 16:00 CEST) and are &lt;strong&gt;live streamed through YouTube&lt;/strong&gt;, and questions are taken through &lt;strong&gt;sli.do&lt;/strong&gt;.&lt;/p&gt;\n\n&lt;p&gt;We continue tomorrow with Benjamin Pierce; title &amp;quot;Backtracking Generators for Random Testing&amp;quot;. All welcome!&lt;/p&gt;\n\n&lt;p&gt;Link to program, including videos of previous talks:&lt;/p&gt;\n\n&lt;p&gt;&lt;a href=\"http://chalmersfp.org/\"&gt;http://chalmersfp.org/&lt;/a&gt;&lt;/p&gt;\n&lt;/div&gt;&lt;!-- SC_ON --&gt;",
          "likes": null,
          "suggested_sort": null,
          "banned_at_utc": null,
          "view_count": null,
          "archived": false,
          "no_follow": false,
          "is_crosspostable": false,
          "pinned": false,
          "over_18": false,
          "all_awardings": [],
          "awarders": [],
          "media_only": false,
          "can_gild": false,
          "spoiler": false,
          "locked": false,
          "author_flair_text": null,
          "treatment_tags": [],
          "visited": false,
          "removed_by": null,
          "num_reports": null,
          "distinguished": null,
          "subreddit_id": "t5_2qh36",
          "mod_reason_by": null,
          "removal_reason": null,
          "link_flair_background_color": "",
          "id": "gld45o",
          "is_robot_indexable": true,
          "report_reasons": null,
          "author": "koenclaessen",
          "discussion_type": null,
          "num_comments": 4,
          "send_replies": true,
          "whitelist_status": "all_ads",
          "contest_mode": false,
          "mod_reports": [],
          "author_patreon_flair": false,
          "author_flair_text_color": null,
          "permalink": "/r/haskell/comments/gld45o/reminder_the_chalmers_online_functional/",
          "parent_whitelist_status": "all_ads",
          "stickied": false,
          "url": "https://old.reddit.com/r/haskell/comments/gld45o/reminder_the_chalmers_online_functional/",
          "subreddit_subscribers": 55194,
          "created_utc": 1589710815,
          "num_crossposts": 0,
          "media": null,
          "is_video": false
        }
      }
    ],
    "after": "t3_gld45o",
    "before": null
  }
}
[T480:~/code/haskell/json]$ cat dat/old.reddit.com-r-haskell-ppp.json \
> | ./bin/json-bytestream-parser
Object
  [ ( "kind" , String "Listing" )
  , ( "data"
    , Object
        [ ( "modhash" , String "" )
        , ( "dist" , Number (26 % 1) )
        , ( "children"
          , Array
              [ Object
                  [ ( "kind" , String "t3" )
                  , ( "data"
                    , Object
                        [ ( "approved_at_utc" , Null )
                        , ( "subreddit" , String "haskell" )
                        , ( "selftext"
                          , String
                              "This is your opportunity to ask any questions you feel don't deserve their own threads, no matter how small or simple they might be!"
                          )
                        , ( "author_fullname" , String "t2_6l4z3" )
                        , ( "saved" , Boolean False )
                        , ( "mod_reason_title" , Null )
                        , ( "gilded" , Number (0 % 1) )
                        , ( "clicked" , Boolean False )
                        , ( "title" , String "Monthly Hask Anything (May 2020)" )
                        , ( "link_flair_richtext" , Array [] )
                        , ( "subreddit_name_prefixed" , String "r/haskell" )
                        , ( "hidden" , Boolean False )
                        , ( "pwls" , Number (6 % 1) )
                        , ( "link_flair_css_class" , Null )
                        , ( "downs" , Number (0 % 1) )
                        , ( "hide_score" , Boolean False )
                        , ( "name" , String "t3_gazovx" )
                        , ( "quarantine" , Boolean False )
                        , ( "link_flair_text_color" , String "dark" )
                        , ( "upvote_ratio" , Number (1080863910568919 % 1125899906842624) )
                        , ( "author_flair_background_color" , Null )
                        , ( "subreddit_type" , String "public" )
                        , ( "ups" , Number (20 % 1) )
                        , ( "total_awards_received" , Number (0 % 1) )
                        , ( "media_embed" , Object [] )
                        , ( "author_flair_template_id" , Null )
                        , ( "is_original_content" , Boolean False )
                        , ( "user_reports" , Array [] )
                        , ( "secure_media" , Null )
                        , ( "is_reddit_media_domain" , Boolean False )
                        , ( "is_meta" , Boolean False )
                        , ( "category" , Null )
                        , ( "secure_media_embed" , Object [] )
                        , ( "link_flair_text" , Null )
                        , ( "can_mod_post" , Boolean False )
                        , ( "score" , Number (20 % 1) )
                        , ( "approved_by" , Null )
                        , ( "author_premium" , Boolean True )
                        , ( "thumbnail" , String "" )
                        , ( "edited" , Boolean False )
                        , ( "author_flair_css_class" , Null )
                        , ( "author_flair_richtext" , Array [] )
                        , ( "gildings" , Object [] )
                        , ( "content_categories" , Null )
                        , ( "is_self" , Boolean True )
                        , ( "mod_note" , Null )
                        , ( "created" , Number (1588295176 % 1) )
                        , ( "link_flair_type" , String "text" )
                        , ( "wls" , Number (6 % 1) )
                        , ( "removed_by_category" , Null )
                        , ( "banned_by" , Null )
                        , ( "author_flair_type" , String "text" )
                        , ( "domain" , String "self.haskell" )
                        , ( "allow_live_comments" , Boolean False )
                        , ( "selftext_html"
                          , String
                              "&lt;!-- SC_OFF --&gt;&lt;div class=\\\"md\\\"&gt;&lt;p&gt;This is your opportunity to ask any questions you feel don&amp;#39;t deserve their own threads, no matter how small or simple they might be!&lt;/p&gt;\\n&lt;/div&gt;&lt;!-- SC_ON --&gt;"
                          )
                        , ( "likes" , Null )
                        , ( "suggested_sort" , String "new" )
                        , ( "banned_at_utc" , Null )
                        , ( "view_count" , Null )
                        , ( "archived" , Boolean False )
                        , ( "no_follow" , Boolean True )
                        , ( "is_crosspostable" , Boolean False )
                        , ( "pinned" , Boolean False )
                        , ( "over_18" , Boolean False )
                        , ( "all_awardings" , Array [] )
                        , ( "awarders" , Array [] )
                        , ( "media_only" , Boolean False )
                        , ( "can_gild" , Boolean False )
                        , ( "spoiler" , Boolean False )
                        , ( "locked" , Boolean False )
                        , ( "author_flair_text" , Null )
                        , ( "treatment_tags" , Array [] )
                        , ( "visited" , Boolean False )
                        , ( "removed_by" , Null )
                        , ( "num_reports" , Null )
                        , ( "distinguished" , String "moderator" )
                        , ( "subreddit_id" , String "t5_2qh36" )
                        , ( "mod_reason_by" , Null )
                        , ( "removal_reason" , Null )
                        , ( "link_flair_background_color" , String "" )
                        , ( "id" , String "gazovx" )
                        , ( "is_robot_indexable" , Boolean True )
                        , ( "report_reasons" , Null )
                        , ( "author" , String "AutoModerator" )
                        , ( "discussion_type" , Null )
                        , ( "num_comments" , Number (228 % 1) )
                        , ( "send_replies" , Boolean False )
                        , ( "whitelist_status" , String "all_ads" )
                        , ( "contest_mode" , Boolean False )
                        , ( "mod_reports" , Array [] )
                        , ( "author_patreon_flair" , Boolean False )
                        , ( "author_flair_text_color" , Null )
                        , ( "permalink"
                          , String
                              "/r/haskell/comments/gazovx/monthly_hask_anything_may_2020/"
                          )
                        , ( "parent_whitelist_status" , String "all_ads" )
                        , ( "stickied" , Boolean True )
                        , ( "url"
                          , String
                              "https://old.reddit.com/r/haskell/comments/gazovx/monthly_hask_anything_may_2020/"
                          )
                        , ( "subreddit_subscribers" , Number (55194 % 1) )
                        , ( "created_utc" , Number (1588266376 % 1) )
                        , ( "num_crossposts" , Number (0 % 1) )
                        , ( "media" , Null )
                        , ( "is_video" , Boolean False )
                        ]
                    )
                  ]
              , Object
                  [ ( "kind" , String "t3" )
                  , ( "data"
                    , Object
                        [ ( "approved_at_utc" , Null )
                        , ( "subreddit" , String "haskell" )
                        , ( "selftext" , String "" )
                        , ( "author_fullname" , String "t2_4iein" )
                        , ( "saved" , Boolean False )
                        , ( "mod_reason_title" , Null )
                        , ( "gilded" , Number (0 % 1) )
                        , ( "clicked" , Boolean False )
                        , ( "title"
                          , String "Haskell Error Message, and How to Improve Them"
                          )
                        , ( "link_flair_richtext" , Array [] )
                        , ( "subreddit_name_prefixed" , String "r/haskell" )
                        , ( "hidden" , Boolean False )
                        , ( "pwls" , Number (6 % 1) )
                        , ( "link_flair_css_class" , Null )
                        , ( "downs" , Number (0 % 1) )
                        , ( "hide_score" , Boolean False )
                        , ( "name" , String "t3_gnblom" )
                        , ( "quarantine" , Boolean False )
                        , ( "link_flair_text_color" , String "dark" )
                        , ( "upvote_ratio" , Number (7836263351624663 % 9007199254740992) )
                        , ( "author_flair_background_color" , Null )
                        , ( "subreddit_type" , String "public" )
                        , ( "ups" , Number (33 % 1) )
                        , ( "total_awards_received" , Number (0 % 1) )
                        , ( "media_embed" , Object [] )
                        , ( "author_flair_template_id" , Null )
                        , ( "is_original_content" , Boolean False )
                        , ( "user_reports" , Array [] )
                        , ( "secure_media" , Null )
                        , ( "is_reddit_media_domain" , Boolean False )
                        , ( "is_meta" , Boolean False )
                        , ( "category" , Null )
                        , ( "secure_media_embed" , Object [] )
                        , ( "link_flair_text" , Null )
                        , ( "can_mod_post" , Boolean False )
                        , ( "score" , Number (33 % 1) )
                        , ( "approved_by" , Null )
                        , ( "author_premium" , Boolean False )
                        , ( "thumbnail" , String "" )
                        , ( "edited" , Boolean False )
                        , ( "author_flair_css_class" , Null )
                        , ( "author_flair_richtext" , Array [] )
                        , ( "gildings" , Object [] )
                        , ( "content_categories" , Null )
                        , ( "is_self" , Boolean False )
                        , ( "mod_note" , Null )
                        , ( "created" , Number (1590011148 % 1) )
                        , ( "link_flair_type" , String "text" )
                        , ( "wls" , Number (6 % 1) )
                        , ( "removed_by_category" , Null )
                        , ( "banned_by" , Null )
                        , ( "author_flair_type" , String "text" )
                        , ( "domain" , String "anthony.noided.media" )
                        , ( "allow_live_comments" , Boolean False )
                        , ( "selftext_html" , Null )
                        , ( "likes" , Null )
                        , ( "suggested_sort" , Null )
                        , ( "banned_at_utc" , Null )
                        , ( "view_count" , Null )
                        , ( "archived" , Boolean False )
                        , ( "no_follow" , Boolean False )
                        , ( "is_crosspostable" , Boolean False )
                        , ( "pinned" , Boolean False )
                        , ( "over_18" , Boolean False )
                        , ( "all_awardings" , Array [] )
                        , ( "awarders" , Array [] )
                        , ( "media_only" , Boolean False )
                        , ( "can_gild" , Boolean False )
                        , ( "spoiler" , Boolean False )
                        , ( "locked" , Boolean False )
                        , ( "author_flair_text" , Null )
                        , ( "treatment_tags" , Array [] )
                        , ( "visited" , Boolean False )
                        , ( "removed_by" , Null )
                        , ( "num_reports" , Null )
                        , ( "distinguished" , Null )
                        , ( "subreddit_id" , String "t5_2qh36" )
                        , ( "mod_reason_by" , Null )
                        , ( "removal_reason" , Null )
                        , ( "link_flair_background_color" , String "" )
                        , ( "id" , String "gnblom" )
                        , ( "is_robot_indexable" , Boolean True )
                        , ( "report_reasons" , Null )
                        , ( "author" , String "THeShinyHObbiest" )
                        , ( "discussion_type" , Null )
                        , ( "num_comments" , Number (32 % 1) )
                        , ( "send_replies" , Boolean True )
                        , ( "whitelist_status" , String "all_ads" )
                        , ( "contest_mode" , Boolean False )
                        , ( "mod_reports" , Array [] )
                        , ( "author_patreon_flair" , Boolean False )
                        , ( "author_flair_text_color" , Null )
                        , ( "permalink"
                          , String
                              "/r/haskell/comments/gnblom/haskell_error_message_and_how_to_improve_them/"
                          )
                        , ( "parent_whitelist_status" , String "all_ads" )
                        , ( "stickied" , Boolean False )
                        , ( "url"
                          , String
                              "https://anthony.noided.media/blog/haskell/programming/2020/05/14/haskell-errors.html"
                          )
                        , ( "subreddit_subscribers" , Number (55194 % 1) )
                        , ( "created_utc" , Number (1589982348 % 1) )
                        , ( "num_crossposts" , Number (0 % 1) )
                        , ( "media" , Null )
                        , ( "is_video" , Boolean False )
                        ]
                    )
                  ]
              , Object
                  [ ( "kind" , String "t3" )
                  , ( "data"
                    , Object
                        [ ( "approved_at_utc" , Null )
                        , ( "subreddit" , String "haskell" )
                        , ( "selftext"
                          , String
                              "Hello dear redditors,\\n\\nI'm happy to announce my book \\\"Functional Design and Architecture\\\".\\n\\nIt's 80% done (8 chapters of 10, 600k symbols), and I decided to start selling it via Leanpub because it's already the most comprehensive guide on building of real software in Haskell and in FP.\\n\\n[Functional Design and Architecture (book) on Leanpub](https://leanpub.com/functional-design-and-architecture)\\n\\nThe book is focussing on many different design patterns, design principles and approaches, but the central role in it plays the approach I call Hierarchical Free Monads. Although the draft of chapters is available online [here](https://graninas.com/functional-design-and-architecture-book/), I won't be uncovering the rest, at least for now. I spent more than 2 years of writing the book, developing the approaches, providing materials and creating showcase projects. And now I think it's not an exaggeration to say that my Hierarchical Free Monads is the most developed approach in Haskell today.\\n\\nThe book is based on 2 projects, so you can play with the concepts easily:\\n\\n* [Hydra](https://github.com/graninas/Hydra), a full-fledged framework for building web services, multithreaded and concurrent applications with SQL and KV DB support. Contains 3 engines: Final Tagless, Free Monad and Church Encoded Free Monad, as well as several demo applications to compare these 3 approaches.\\n* [Andromeda](https://github.com/graninas/Andromeda), a SCADA software for spaceship control.\\n\\nI also have a Patreon program for the book:\\n\\n[Patreon: \\\"Functional Design and Architecture\\\"](https://www.patreon.com/functional_design_and_architecture)\\n\\nAll the money collected from this program will be used to hire professional editors, designers, reviewers. I'm very grateful to all my Patron supporters! The supporters have an access to some exclusive content. They will get a edited book as well.\\n\\nThe following project is of my design also.\\n\\n* [Node](https://github.com/graninas/Node), a real-world all-in-one framework which is tested in production. It allows to build network actors and blockchain protocols, console applications, work with KV database and cryptography. Sample but not simple blockchain applications are also provided there.\\n\\nYou can get familiar with my long read articles explaining the concepts in details:\\n\\n* [Hierarchical Free Monads: The Most Developed Approach In Haskell (article)](https://github.com/graninas/hierarchical-free-monads-the-most-developed-approach-in-haskell)\\n* [Automatic White-Box Testing with Free Monads (article, showcase)](https://github.com/graninas/automatic-whitebox-testing-showcase)\\n* [Building network actors with Node Framework](https://gist.github.com/graninas/9beb8df5d88dda5fa21c47ce9bcb0e16)\\n\\nYou might also want to get familiar with my [list of materials on Software Design in Haskell](https://github.com/graninas/software-design-in-haskell).\\n\\nI'm also giving talks on this topic. Consider the following talks:\\n\\n* [Hierarchical Free Monads and Software Design in Functional Programming (talk)](https://www.youtube.com/watch?v=3GKQ4ni2pS0)\\n* [Automatic Whitebox Testing with Free Monads (talk)](https://www.youtube.com/watch?v=ciZL-adDpVQ)\\n* [Final Tagless vs Free Monads (talk, Russian)](https://www.youtube.com/watch?v=u1GGqDQyGfc) | [slides (English)](https://drive.google.com/open?id=1VhS8ySgk2w5RoN_l_Ar_axcE4Dzf97zLw1uuzUJQbCo)\\n\\nAnd this list of my materials is not even complete. For the record, I used Free Monads for making my own STM library: in Haskell and in C++. The implementation was incredibly simple due to the power of Free Monads to abstract things. There are different projects:\\n\\n* [stm-free](https://github.com/graninas/stm-free), my Free Monad based STM library in Haskell;\\n* [cpp\\\\_stm-free](https://github.com/graninas/cpp_stm_free), the port to C++. Even more, it has 2 independent engines: Free Monad based and Church Encoded Free Monad based.\\n* [Software Transactional Memory in C++: pure functional approach (Tutorial)](https://gist.github.com/graninas/c7e0a603f3a22c7e85daa4599bf92525) \\\\- the article, in case you like strange functional programming in C++.\\n* [Functional Approach To Software Transactional Memory in C++ (talk, Russian)](https://www.youtube.com/watch?v=VHZPcz8HwZs) | [slides](https://docs.google.com/presentation/d/1_znOLZDKruKRNLA58TDlnXYQjTg9sXNJHPOLHfDTjeU/edit?usp=sharing) (English)\\n* [cpp\\\\_parsec\\\\_free](https://github.com/graninas/cpp_parsec_free): a PoC of monadic parsers in C++ based on the same idea of Free Monads.\\n* [Monadic Parsers in C++ (talk, Russian)](https://www.youtube.com/watch?v=q39PHTJDaLE) | [slides](https://docs.google.com/presentation/d/1zlwKBX8-DYVWUYmzvmKm7ggDVBugEJzY6OFSWjeQOA4/edit?usp=sharing) (English)\\n* [hinteractive](https://github.com/graninas/hinteractive), an eDSL-like engine for interactive fiction games like Zork. Free Monad based.\\n\\nYes, all these projects show that I investigated Free Monads from all possible sides. But even more, there are two open source frameworks I (with my coworkers) designed for our employer, and these projects are heavily used in production:\\n\\n* [PureScript Presto](https://github.com/juspay/purescript-presto) \\\\- a framework for building mobile apps using a handy eDSL.\\n* [PureScript Presto.Backend](https://github.com/juspay/purescript-presto-backend) \\\\- a framework for web RESTful backends.\\n\\nStill not convinced? Follow me ([Twitter](https://twitter.com/graninas), [GitHub](https://github.com/graninas), [LinkedIn](https://www.linkedin.com/in/alexander-granin-46889236/), [Telegram](https://web.telegram.org/#/im?p=@graninas), [Facebook](https://www.facebook.com/alexandr.granin)), hire me, and keep your eyes on my activity. Even more materials are coming!\\n\\nYours truly,\\n\\nAlexander Granin"
                          )
                        , ( "author_fullname" , String "t2_geqys" )
                        , ( "saved" , Boolean False )
                        , ( "mod_reason_title" , Null )
                        , ( "gilded" , Number (0 % 1) )
                        , ( "clicked" , Boolean False )
                        , ( "title"
                          , String "Book \\\"Functional Design and Architecture\\\""
                          )
                        , ( "link_flair_richtext" , Array [] )
                        , ( "subreddit_name_prefixed" , String "r/haskell" )
                        , ( "hidden" , Boolean False )
                        , ( "pwls" , Number (6 % 1) )
                        , ( "link_flair_css_class" , Null )
                        , ( "downs" , Number (0 % 1) )
                        , ( "hide_score" , Boolean False )
                        , ( "name" , String "t3_gmxfqz" )
                        , ( "quarantine" , Boolean False )
                        , ( "link_flair_text_color" , String "dark" )
                        , ( "upvote_ratio" , Number (4368491638549381 % 4503599627370496) )
                        , ( "author_flair_background_color" , Null )
                        , ( "subreddit_type" , String "public" )
                        , ( "ups" , Number (152 % 1) )
                        , ( "total_awards_received" , Number (1 % 1) )
                        , ( "media_embed" , Object [] )
                        , ( "author_flair_template_id" , Null )
                        , ( "is_original_content" , Boolean False )
                        , ( "user_reports" , Array [] )
                        , ( "secure_media" , Null )
                        , ( "is_reddit_media_domain" , Boolean False )
                        , ( "is_meta" , Boolean False )
                        , ( "category" , Null )
                        , ( "secure_media_embed" , Object [] )
                        , ( "link_flair_text" , Null )
                        , ( "can_mod_post" , Boolean False )
                        , ( "score" , Number (152 % 1) )
                        , ( "approved_by" , Null )
                        , ( "author_premium" , Boolean False )
                        , ( "thumbnail" , String "" )
                        , ( "edited" , Number (1589979013 % 1) )
                        , ( "author_flair_css_class" , Null )
                        , ( "author_flair_richtext" , Array [] )
                        , ( "gildings" , Object [] )
                        , ( "content_categories" , Null )
                        , ( "is_self" , Boolean True )
                        , ( "mod_note" , Null )
                        , ( "created" , Number (1589951620 % 1) )
                        , ( "link_flair_type" , String "text" )
                        , ( "wls" , Number (6 % 1) )
                        , ( "removed_by_category" , Null )
                        , ( "banned_by" , Null )
                        , ( "author_flair_type" , String "text" )
                        , ( "domain" , String "self.haskell" )
                        , ( "allow_live_comments" , Boolean False )
                        , ( "selftext_html"
                          , String
                              "&lt;!-- SC_OFF --&gt;&lt;div class=\\\"md\\\"&gt;&lt;p&gt;Hello dear redditors,&lt;/p&gt;\\n\\n&lt;p&gt;I&amp;#39;m happy to announce my book &amp;quot;Functional Design and Architecture&amp;quot;.&lt;/p&gt;\\n\\n&lt;p&gt;It&amp;#39;s 80% done (8 chapters of 10, 600k symbols), and I decided to start selling it via Leanpub because it&amp;#39;s already the most comprehensive guide on building of real software in Haskell and in FP.&lt;/p&gt;\\n\\n&lt;p&gt;&lt;a href=\\\"https://leanpub.com/functional-design-and-architecture\\\"&gt;Functional Design and Architecture (book) on Leanpub&lt;/a&gt;&lt;/p&gt;\\n\\n&lt;p&gt;The book is focussing on many different design patterns, design principles and approaches, but the central role in it plays the approach I call Hierarchical Free Monads. Although the draft of chapters is available online &lt;a href=\\\"https://graninas.com/functional-design-and-architecture-book/\\\"&gt;here&lt;/a&gt;, I won&amp;#39;t be uncovering the rest, at least for now. I spent more than 2 years of writing the book, developing the approaches, providing materials and creating showcase projects. And now I think it&amp;#39;s not an exaggeration to say that my Hierarchical Free Monads is the most developed approach in Haskell today.&lt;/p&gt;\\n\\n&lt;p&gt;The book is based on 2 projects, so you can play with the concepts easily:&lt;/p&gt;\\n\\n&lt;ul&gt;\\n&lt;li&gt;&lt;a href=\\\"https://github.com/graninas/Hydra\\\"&gt;Hydra&lt;/a&gt;, a full-fledged framework for building web services, multithreaded and concurrent applications with SQL and KV DB support. Contains 3 engines: Final Tagless, Free Monad and Church Encoded Free Monad, as well as several demo applications to compare these 3 approaches.&lt;/li&gt;\\n&lt;li&gt;&lt;a href=\\\"https://github.com/graninas/Andromeda\\\"&gt;Andromeda&lt;/a&gt;, a SCADA software for spaceship control.&lt;/li&gt;\\n&lt;/ul&gt;\\n\\n&lt;p&gt;I also have a Patreon program for the book:&lt;/p&gt;\\n\\n&lt;p&gt;&lt;a href=\\\"https://www.patreon.com/functional_design_and_architecture\\\"&gt;Patreon: &amp;quot;Functional Design and Architecture&amp;quot;&lt;/a&gt;&lt;/p&gt;\\n\\n&lt;p&gt;All the money collected from this program will be used to hire professional editors, designers, reviewers. I&amp;#39;m very grateful to all my Patron supporters! The supporters have an access to some exclusive content. They will get a edited book as well.&lt;/p&gt;\\n\\n&lt;p&gt;The following project is of my design also.&lt;/p&gt;\\n\\n&lt;ul&gt;\\n&lt;li&gt;&lt;a href=\\\"https://github.com/graninas/Node\\\"&gt;Node&lt;/a&gt;, a real-world all-in-one framework which is tested in production. It allows to build network actors and blockchain protocols, console applications, work with KV database and cryptography. Sample but not simple blockchain applications are also provided there.&lt;/li&gt;\\n&lt;/ul&gt;\\n\\n&lt;p&gt;You can get familiar with my long read articles explaining the concepts in details:&lt;/p&gt;\\n\\n&lt;ul&gt;\\n&lt;li&gt;&lt;a href=\\\"https://github.com/graninas/hierarchical-free-monads-the-most-developed-approach-in-haskell\\\"&gt;Hierarchical Free Monads: The Most Developed Approach In Haskell (article)&lt;/a&gt;&lt;/li&gt;\\n&lt;li&gt;&lt;a href=\\\"https://github.com/graninas/automatic-whitebox-testing-showcase\\\"&gt;Automatic White-Box Testing with Free Monads (article, showcase)&lt;/a&gt;&lt;/li&gt;\\n&lt;li&gt;&lt;a href=\\\"https://gist.github.com/graninas/9beb8df5d88dda5fa21c47ce9bcb0e16\\\"&gt;Building network actors with Node Framework&lt;/a&gt;&lt;/li&gt;\\n&lt;/ul&gt;\\n\\n&lt;p&gt;You might also want to get familiar with my &lt;a href=\\\"https://github.com/graninas/software-design-in-haskell\\\"&gt;list of materials on Software Design in Haskell&lt;/a&gt;.&lt;/p&gt;\\n\\n&lt;p&gt;I&amp;#39;m also giving talks on this topic. Consider the following talks:&lt;/p&gt;\\n\\n&lt;ul&gt;\\n&lt;li&gt;&lt;a href=\\\"https://www.youtube.com/watch?v=3GKQ4ni2pS0\\\"&gt;Hierarchical Free Monads and Software Design in Functional Programming (talk)&lt;/a&gt;&lt;/li&gt;\\n&lt;li&gt;&lt;a href=\\\"https://www.youtube.com/watch?v=ciZL-adDpVQ\\\"&gt;Automatic Whitebox Testing with Free Monads (talk)&lt;/a&gt;&lt;/li&gt;\\n&lt;li&gt;&lt;a href=\\\"https://www.youtube.com/watch?v=u1GGqDQyGfc\\\"&gt;Final Tagless vs Free Monads (talk, Russian)&lt;/a&gt; | &lt;a href=\\\"https://drive.google.com/open?id=1VhS8ySgk2w5RoN_l_Ar_axcE4Dzf97zLw1uuzUJQbCo\\\"&gt;slides (English)&lt;/a&gt;&lt;/li&gt;\\n&lt;/ul&gt;\\n\\n&lt;p&gt;And this list of my materials is not even complete. For the record, I used Free Monads for making my own STM library: in Haskell and in C++. The implementation was incredibly simple due to the power of Free Monads to abstract things. There are different projects:&lt;/p&gt;\\n\\n&lt;ul&gt;\\n&lt;li&gt;&lt;a href=\\\"https://github.com/graninas/stm-free\\\"&gt;stm-free&lt;/a&gt;, my Free Monad based STM library in Haskell;&lt;/li&gt;\\n&lt;li&gt;&lt;a href=\\\"https://github.com/graninas/cpp_stm_free\\\"&gt;cpp_stm-free&lt;/a&gt;, the port to C++. Even more, it has 2 independent engines: Free Monad based and Church Encoded Free Monad based.&lt;/li&gt;\\n&lt;li&gt;&lt;a href=\\\"https://gist.github.com/graninas/c7e0a603f3a22c7e85daa4599bf92525\\\"&gt;Software Transactional Memory in C++: pure functional approach (Tutorial)&lt;/a&gt; - the article, in case you like strange functional programming in C++.&lt;/li&gt;\\n&lt;li&gt;&lt;a href=\\\"https://www.youtube.com/watch?v=VHZPcz8HwZs\\\"&gt;Functional Approach To Software Transactional Memory in C++ (talk, Russian)&lt;/a&gt; | &lt;a href=\\\"https://docs.google.com/presentation/d/1_znOLZDKruKRNLA58TDlnXYQjTg9sXNJHPOLHfDTjeU/edit?usp=sharing\\\"&gt;slides&lt;/a&gt; (English)&lt;/li&gt;\\n&lt;li&gt;&lt;a href=\\\"https://github.com/graninas/cpp_parsec_free\\\"&gt;cpp_parsec_free&lt;/a&gt;: a PoC of monadic parsers in C++ based on the same idea of Free Monads.&lt;/li&gt;\\n&lt;li&gt;&lt;a href=\\\"https://www.youtube.com/watch?v=q39PHTJDaLE\\\"&gt;Monadic Parsers in C++ (talk, Russian)&lt;/a&gt; | &lt;a href=\\\"https://docs.google.com/presentation/d/1zlwKBX8-DYVWUYmzvmKm7ggDVBugEJzY6OFSWjeQOA4/edit?usp=sharing\\\"&gt;slides&lt;/a&gt; (English)&lt;/li&gt;\\n&lt;li&gt;&lt;a href=\\\"https://github.com/graninas/hinteractive\\\"&gt;hinteractive&lt;/a&gt;, an eDSL-like engine for interactive fiction games like Zork. Free Monad based.&lt;/li&gt;\\n&lt;/ul&gt;\\n\\n&lt;p&gt;Yes, all these projects show that I investigated Free Monads from all possible sides. But even more, there are two open source frameworks I (with my coworkers) designed for our employer, and these projects are heavily used in production:&lt;/p&gt;\\n\\n&lt;ul&gt;\\n&lt;li&gt;&lt;a href=\\\"https://github.com/juspay/purescript-presto\\\"&gt;PureScript Presto&lt;/a&gt; - a framework for building mobile apps using a handy eDSL.&lt;/li&gt;\\n&lt;li&gt;&lt;a href=\\\"https://github.com/juspay/purescript-presto-backend\\\"&gt;PureScript Presto.Backend&lt;/a&gt; - a framework for web RESTful backends.&lt;/li&gt;\\n&lt;/ul&gt;\\n\\n&lt;p&gt;Still not convinced? Follow me (&lt;a href=\\\"https://twitter.com/graninas\\\"&gt;Twitter&lt;/a&gt;, &lt;a href=\\\"https://github.com/graninas\\\"&gt;GitHub&lt;/a&gt;, &lt;a href=\\\"https://www.linkedin.com/in/alexander-granin-46889236/\\\"&gt;LinkedIn&lt;/a&gt;, &lt;a href=\\\"https://web.telegram.org/#/im?p=@graninas\\\"&gt;Telegram&lt;/a&gt;, &lt;a href=\\\"https://www.facebook.com/alexandr.granin\\\"&gt;Facebook&lt;/a&gt;), hire me, and keep your eyes on my activity. Even more materials are coming!&lt;/p&gt;\\n\\n&lt;p&gt;Yours truly,&lt;/p&gt;\\n\\n&lt;p&gt;Alexander Granin&lt;/p&gt;\\n&lt;/div&gt;&lt;!-- SC_ON --&gt;"
                          )
                        , ( "likes" , Null )
                        , ( "suggested_sort" , Null )
                        , ( "banned_at_utc" , Null )
                        , ( "view_count" , Null )
                        , ( "archived" , Boolean False )
                        , ( "no_follow" , Boolean False )
                        , ( "is_crosspostable" , Boolean False )
                        , ( "pinned" , Boolean False )
                        , ( "over_18" , Boolean False )
                        , ( "all_awardings"
                          , Array
                              [ Object
                                  [ ( "giver_coin_reward" , Null )
                                  , ( "subreddit_id" , Null )
                                  , ( "is_new" , Boolean False )
                                  , ( "days_of_drip_extension" , Number (0 % 1) )
                                  , ( "coin_price" , Number (500 % 1) )
                                  , ( "id" , String "award_43c43a35-15c5-4f73-91ef-fe538426435a" )
                                  , ( "penny_donate" , Null )
                                  , ( "coin_reward" , Number (100 % 1) )
                                  , ( "icon_url"
                                    , String
                                        "https://i.redd.it/award_images/t5_22cerq/xe5mw55w5v541_BlessUp.png"
                                    )
                                  , ( "days_of_premium" , Number (0 % 1) )
                                  , ( "icon_height" , Number (2048 % 1) )
                                  , ( "resized_icons"
                                    , Array
                                        [ Object
                                            [ ( "url"
                                              , String
                                                  "https://preview.redd.it/award_images/t5_22cerq/xe5mw55w5v541_BlessUp.png?width=16&amp;height=16&amp;auto=webp&amp;s=e84e08de4b1352e679d612c063584341f56bc2b5"
                                              )
                                            , ( "width" , Number (16 % 1) )
                                            , ( "height" , Number (16 % 1) )
                                            ]
                                        , Object
                                            [ ( "url"
                                              , String
                                                  "https://preview.redd.it/award_images/t5_22cerq/xe5mw55w5v541_BlessUp.png?width=32&amp;height=32&amp;auto=webp&amp;s=d01d7a3286bb55c235e217736c78c66e2d7d0c18"
                                              )
                                            , ( "width" , Number (32 % 1) )
                                            , ( "height" , Number (32 % 1) )
                                            ]
                                        , Object
                                            [ ( "url"
                                              , String
                                                  "https://preview.redd.it/award_images/t5_22cerq/xe5mw55w5v541_BlessUp.png?width=48&amp;height=48&amp;auto=webp&amp;s=6ae7d390be614e44f1ec06141d0ba51d65494bff"
                                              )
                                            , ( "width" , Number (48 % 1) )
                                            , ( "height" , Number (48 % 1) )
                                            ]
                                        , Object
                                            [ ( "url"
                                              , String
                                                  "https://preview.redd.it/award_images/t5_22cerq/xe5mw55w5v541_BlessUp.png?width=64&amp;height=64&amp;auto=webp&amp;s=1c88befd3d95c2ea37b95a7132db98d8a8730ae1"
                                              )
                                            , ( "width" , Number (64 % 1) )
                                            , ( "height" , Number (64 % 1) )
                                            ]
                                        , Object
                                            [ ( "url"
                                              , String
                                                  "https://preview.redd.it/award_images/t5_22cerq/xe5mw55w5v541_BlessUp.png?width=128&amp;height=128&amp;auto=webp&amp;s=f97d6987f6545f6cb659f1fce7c304278a92f762"
                                              )
                                            , ( "width" , Number (128 % 1) )
                                            , ( "height" , Number (128 % 1) )
                                            ]
                                        ]
                                    )
                                  , ( "icon_width" , Number (2048 % 1) )
                                  , ( "start_date" , Null )
                                  , ( "is_enabled" , Boolean True )
                                  , ( "description"
                                    , String
                                        "Prayers up for the blessed. Gives %{coin_symbol}100 Coins to both the author and the community."
                                    )
                                  , ( "end_date" , Null )
                                  , ( "subreddit_coin_reward" , Number (100 % 1) )
                                  , ( "count" , Number (1 % 1) )
                                  , ( "name" , String "Bless Up (Pro)" )
                                  , ( "icon_format" , Null )
                                  , ( "award_sub_type" , String "GLOBAL" )
                                  , ( "penny_price" , Null )
                                  , ( "award_type" , String "global" )
                                  ]
                              ]
                          )
                        , ( "awarders" , Array [] )
                        , ( "media_only" , Boolean False )
                        , ( "can_gild" , Boolean False )
                        , ( "spoiler" , Boolean False )
                        , ( "locked" , Boolean False )
                        , ( "author_flair_text" , Null )
                        , ( "treatment_tags" , Array [] )
                        , ( "visited" , Boolean False )
                        , ( "removed_by" , Null )
                        , ( "num_reports" , Null )
                        , ( "distinguished" , Null )
                        , ( "subreddit_id" , String "t5_2qh36" )
                        , ( "mod_reason_by" , Null )
                        , ( "removal_reason" , Null )
                        , ( "link_flair_background_color" , String "" )
                        , ( "id" , String "gmxfqz" )
                        , ( "is_robot_indexable" , Boolean True )
                        , ( "report_reasons" , Null )
                        , ( "author" , String "graninas" )
                        , ( "discussion_type" , Null )
                        , ( "num_comments" , Number (26 % 1) )
                        , ( "send_replies" , Boolean True )
                        , ( "whitelist_status" , String "all_ads" )
                        , ( "contest_mode" , Boolean False )
                        , ( "mod_reports" , Array [] )
                        , ( "author_patreon_flair" , Boolean False )
                        , ( "author_flair_text_color" , Null )
                        , ( "permalink"
                          , String
                              "/r/haskell/comments/gmxfqz/book_functional_design_and_architecture/"
                          )
                        , ( "parent_whitelist_status" , String "all_ads" )
                        , ( "stickied" , Boolean False )
                        , ( "url"
                          , String
                              "https://old.reddit.com/r/haskell/comments/gmxfqz/book_functional_design_and_architecture/"
                          )
                        , ( "subreddit_subscribers" , Number (55194 % 1) )
                        , ( "created_utc" , Number (1589922820 % 1) )
                        , ( "num_crossposts" , Number (2 % 1) )
                        , ( "media" , Null )
                        , ( "is_video" , Boolean False )
                        ]
                    )
                  ]
              , Object
                  [ ( "kind" , String "t3" )
                  , ( "data"
                    , Object
                        [ ( "approved_at_utc" , Null )
                        , ( "subreddit" , String "haskell" )
                        , ( "selftext" , String "" )
                        , ( "author_fullname" , String "t2_3qjdu" )
                        , ( "saved" , Boolean False )
                        , ( "mod_reason_title" , Null )
                        , ( "gilded" , Number (0 % 1) )
                        , ( "clicked" , Boolean False )
                        , ( "title" , String "DerivingVia sums-of-products" )
                        , ( "link_flair_richtext" , Array [] )
                        , ( "subreddit_name_prefixed" , String "r/haskell" )
                        , ( "hidden" , Boolean False )
                        , ( "pwls" , Number (6 % 1) )
                        , ( "link_flair_css_class" , Null )
                        , ( "downs" , Number (0 % 1) )
                        , ( "hide_score" , Boolean False )
                        , ( "name" , String "t3_gn8c5r" )
                        , ( "quarantine" , Boolean False )
                        , ( "link_flair_text_color" , String "dark" )
                        , ( "upvote_ratio" , Number (4278419646001971 % 4503599627370496) )
                        , ( "author_flair_background_color" , Null )
                        , ( "subreddit_type" , String "public" )
                        , ( "ups" , Number (15 % 1) )
                        , ( "total_awards_received" , Number (0 % 1) )
                        , ( "media_embed" , Object [] )
                        , ( "author_flair_template_id" , Null )
                        , ( "is_original_content" , Boolean False )
                        , ( "user_reports" , Array [] )
                        , ( "secure_media" , Null )
                        , ( "is_reddit_media_domain" , Boolean False )
                        , ( "is_meta" , Boolean False )
                        , ( "category" , Null )
                        , ( "secure_media_embed" , Object [] )
                        , ( "link_flair_text" , Null )
                        , ( "can_mod_post" , Boolean False )
                        , ( "score" , Number (15 % 1) )
                        , ( "approved_by" , Null )
                        , ( "author_premium" , Boolean False )
                        , ( "thumbnail" , String "" )
                        , ( "edited" , Boolean False )
                        , ( "author_flair_css_class" , Null )
                        , ( "author_flair_richtext" , Array [] )
                        , ( "gildings" , Object [] )
                        , ( "content_categories" , Null )
                        , ( "is_self" , Boolean False )
                        , ( "mod_note" , Null )
                        , ( "created" , Number (1589996118 % 1) )
                        , ( "link_flair_type" , String "text" )
                        , ( "wls" , Number (6 % 1) )
                        , ( "removed_by_category" , Null )
                        , ( "banned_by" , Null )
                        , ( "author_flair_type" , String "text" )
                        , ( "domain" , String "iceland_jack.brick.do" )
                        , ( "allow_live_comments" , Boolean False )
                        , ( "selftext_html" , Null )
                        , ( "likes" , Null )
                        , ( "suggested_sort" , Null )
                        , ( "banned_at_utc" , Null )
                        , ( "view_count" , Null )
                        , ( "archived" , Boolean False )
                        , ( "no_follow" , Boolean False )
                        , ( "is_crosspostable" , Boolean False )
                        , ( "pinned" , Boolean False )
                        , ( "over_18" , Boolean False )
                        , ( "all_awardings" , Array [] )
                        , ( "awarders" , Array [] )
                        , ( "media_only" , Boolean False )
                        , ( "can_gild" , Boolean False )
                        , ( "spoiler" , Boolean False )
                        , ( "locked" , Boolean False )
                        , ( "author_flair_text" , Null )
                        , ( "treatment_tags" , Array [] )
                        , ( "visited" , Boolean False )
                        , ( "removed_by" , Null )
                        , ( "num_reports" , Null )
                        , ( "distinguished" , Null )
                        , ( "subreddit_id" , String "t5_2qh36" )
                        , ( "mod_reason_by" , Null )
                        , ( "removal_reason" , Null )
                        , ( "link_flair_background_color" , String "" )
                        , ( "id" , String "gn8c5r" )
                        , ( "is_robot_indexable" , Boolean True )
                        , ( "report_reasons" , Null )
                        , ( "author" , String "Iceland_jack" )
                        , ( "discussion_type" , Null )
                        , ( "num_comments" , Number (5 % 1) )
                        , ( "send_replies" , Boolean True )
                        , ( "whitelist_status" , String "all_ads" )
                        , ( "contest_mode" , Boolean False )
                        , ( "mod_reports" , Array [] )
                        , ( "author_patreon_flair" , Boolean False )
                        , ( "author_flair_text_color" , Null )
                        , ( "permalink"
                          , String "/r/haskell/comments/gn8c5r/derivingvia_sumsofproducts/"
                          )
                        , ( "parent_whitelist_status" , String "all_ads" )
                        , ( "stickied" , Boolean False )
                        , ( "url"
                          , String
                              "https://iceland_jack.brick.do/e28e745c-40b8-4b0b-8148-1f1ae0c32d43"
                          )
                        , ( "subreddit_subscribers" , Number (55194 % 1) )
                        , ( "created_utc" , Number (1589967318 % 1) )
                        , ( "num_crossposts" , Number (0 % 1) )
                        , ( "media" , Null )
                        , ( "is_video" , Boolean False )
                        ]
                    )
                  ]
              , Object
                  [ ( "kind" , String "t3" )
                  , ( "data"
                    , Object
                        [ ( "approved_at_utc" , Null )
                        , ( "subreddit" , String "haskell" )
                        , ( "selftext" , String "" )
                        , ( "author_fullname" , String "t2_jxviuup" )
                        , ( "saved" , Boolean False )
                        , ( "mod_reason_title" , Null )
                        , ( "gilded" , Number (0 % 1) )
                        , ( "clicked" , Boolean False )
                        , ( "title"
                          , String
                              "Alejandro Serrano Mena on Why Functors and Applicatives Compose but Monads Don't"
                          )
                        , ( "link_flair_richtext" , Array [] )
                        , ( "subreddit_name_prefixed" , String "r/haskell" )
                        , ( "hidden" , Boolean False )
                        , ( "pwls" , Number (6 % 1) )
                        , ( "link_flair_css_class" , Null )
                        , ( "downs" , Number (0 % 1) )
                        , ( "hide_score" , Boolean False )
                        , ( "name" , String "t3_gn2tqs" )
                        , ( "quarantine" , Boolean False )
                        , ( "link_flair_text_color" , String "dark" )
                        , ( "upvote_ratio" , Number (2206763817411543 % 2251799813685248) )
                        , ( "author_flair_background_color" , Null )
                        , ( "subreddit_type" , String "public" )
                        , ( "ups" , Number (52 % 1) )
                        , ( "total_awards_received" , Number (0 % 1) )
                        , ( "media_embed"
                          , Object
                              [ ( "content"
                                , String
                                    "&lt;iframe width=\\\"600\\\" height=\\\"338\\\" src=\\\"https://www.youtube.com/embed/eZ9FpG8May8?feature=oembed&amp;enablejsapi=1\\\" frameborder=\\\"0\\\" allow=\\\"accelerometer; autoplay; encrypted-media; gyroscope; picture-in-picture\\\" allowfullscreen&gt;&lt;/iframe&gt;"
                                )
                              , ( "width" , Number (600 % 1) )
                              , ( "scrolling" , Boolean False )
                              , ( "height" , Number (338 % 1) )
                              ]
                          )
                        , ( "author_flair_template_id" , Null )
                        , ( "is_original_content" , Boolean False )
                        , ( "user_reports" , Array [] )
                        , ( "secure_media"
                          , Object
                              [ ( "type" , String "youtube.com" )
                              , ( "oembed"
                                , Object
                                    [ ( "provider_url" , String "https://www.youtube.com/" )
                                    , ( "version" , String "1.0" )
                                    , ( "title"
                                      , String
                                          "Alejandro Serrano Mena on Why Functors and Applicatives Compose but Monads Don't"
                                      )
                                    , ( "type" , String "video" )
                                    , ( "thumbnail_width" , Number (480 % 1) )
                                    , ( "height" , Number (338 % 1) )
                                    , ( "width" , Number (600 % 1) )
                                    , ( "html"
                                      , String
                                          "&lt;iframe width=\\\"600\\\" height=\\\"338\\\" src=\\\"https://www.youtube.com/embed/eZ9FpG8May8?feature=oembed&amp;enablejsapi=1\\\" frameborder=\\\"0\\\" allow=\\\"accelerometer; autoplay; encrypted-media; gyroscope; picture-in-picture\\\" allowfullscreen&gt;&lt;/iframe&gt;"
                                      )
                                    , ( "author_name"
                                      , String "Berlin Functional Programming Group"
                                      )
                                    , ( "provider_name" , String "YouTube" )
                                    , ( "thumbnail_url"
                                      , String "https://i.ytimg.com/vi/eZ9FpG8May8/hqdefault.jpg"
                                      )
                                    , ( "thumbnail_height" , Number (360 % 1) )
                                    , ( "author_url"
                                      , String
                                          "https://www.youtube.com/channel/UCNp-DVb8cQRIOo32sZhWgNg"
                                      )
                                    ]
                                )
                              ]
                          )
                        , ( "is_reddit_media_domain" , Boolean False )
                        , ( "is_meta" , Boolean False )
                        , ( "category" , Null )
                        , ( "secure_media_embed"
                          , Object
                              [ ( "content"
                                , String
                                    "&lt;iframe width=\\\"600\\\" height=\\\"338\\\" src=\\\"https://www.youtube.com/embed/eZ9FpG8May8?feature=oembed&amp;enablejsapi=1\\\" frameborder=\\\"0\\\" allow=\\\"accelerometer; autoplay; encrypted-media; gyroscope; picture-in-picture\\\" allowfullscreen&gt;&lt;/iframe&gt;"
                                )
                              , ( "width" , Number (600 % 1) )
                              , ( "scrolling" , Boolean False )
                              , ( "media_domain_url"
                                , String "https://www.redditmedia.com/mediaembed/gn2tqs"
                                )
                              , ( "height" , Number (338 % 1) )
                              ]
                          )
                        , ( "link_flair_text" , Null )
                        , ( "can_mod_post" , Boolean False )
                        , ( "score" , Number (52 % 1) )
                        , ( "approved_by" , Null )
                        , ( "author_premium" , Boolean False )
                        , ( "thumbnail" , String "" )
                        , ( "edited" , Boolean False )
                        , ( "author_flair_css_class" , Null )
                        , ( "author_flair_richtext" , Array [] )
                        , ( "gildings" , Object [] )
                        , ( "content_categories" , Null )
                        , ( "is_self" , Boolean False )
                        , ( "mod_note" , Null )
                        , ( "created" , Number (1589970172 % 1) )
                        , ( "link_flair_type" , String "text" )
                        , ( "wls" , Number (6 % 1) )
                        , ( "removed_by_category" , Null )
                        , ( "banned_by" , Null )
                        , ( "author_flair_type" , String "text" )
                        , ( "domain" , String "youtube.com" )
                        , ( "allow_live_comments" , Boolean False )
                        , ( "selftext_html" , Null )
                        , ( "likes" , Null )
                        , ( "suggested_sort" , Null )
                        , ( "banned_at_utc" , Null )
                        , ( "view_count" , Null )
                        , ( "archived" , Boolean False )
                        , ( "no_follow" , Boolean False )
                        , ( "is_crosspostable" , Boolean False )
                        , ( "pinned" , Boolean False )
                        , ( "over_18" , Boolean False )
                        , ( "all_awardings" , Array [] )
                        , ( "awarders" , Array [] )
                        , ( "media_only" , Boolean False )
                        , ( "can_gild" , Boolean False )
                        , ( "spoiler" , Boolean False )
                        , ( "locked" , Boolean False )
                        , ( "author_flair_text" , Null )
                        , ( "treatment_tags" , Array [] )
                        , ( "visited" , Boolean False )
                        , ( "removed_by" , Null )
                        , ( "num_reports" , Null )
                        , ( "distinguished" , Null )
                        , ( "subreddit_id" , String "t5_2qh36" )
                        , ( "mod_reason_by" , Null )
                        , ( "removal_reason" , Null )
                        , ( "link_flair_background_color" , String "" )
                        , ( "id" , String "gn2tqs" )
                        , ( "is_robot_indexable" , Boolean True )
                        , ( "report_reasons" , Null )
                        , ( "author" , String "iedoub" )
                        , ( "discussion_type" , Null )
                        , ( "num_comments" , Number (5 % 1) )
                        , ( "send_replies" , Boolean True )
                        , ( "whitelist_status" , String "all_ads" )
                        , ( "contest_mode" , Boolean False )
                        , ( "mod_reports" , Array [] )
                        , ( "author_patreon_flair" , Boolean False )
                        , ( "author_flair_text_color" , Null )
                        , ( "permalink"
                          , String
                              "/r/haskell/comments/gn2tqs/alejandro_serrano_mena_on_why_functors_and/"
                          )
                        , ( "parent_whitelist_status" , String "all_ads" )
                        , ( "stickied" , Boolean False )
                        , ( "url"
                          , String
                              "https://www.youtube.com/watch?v=eZ9FpG8May8&amp;feature=youtu.be"
                          )
                        , ( "subreddit_subscribers" , Number (55194 % 1) )
                        , ( "created_utc" , Number (1589941372 % 1) )
                        , ( "num_crossposts" , Number (0 % 1) )
                        , ( "media"
                          , Object
                              [ ( "type" , String "youtube.com" )
                              , ( "oembed"
                                , Object
                                    [ ( "provider_url" , String "https://www.youtube.com/" )
                                    , ( "version" , String "1.0" )
                                    , ( "title"
                                      , String
                                          "Alejandro Serrano Mena on Why Functors and Applicatives Compose but Monads Don't"
                                      )
                                    , ( "type" , String "video" )
                                    , ( "thumbnail_width" , Number (480 % 1) )
                                    , ( "height" , Number (338 % 1) )
                                    , ( "width" , Number (600 % 1) )
                                    , ( "html"
                                      , String
                                          "&lt;iframe width=\\\"600\\\" height=\\\"338\\\" src=\\\"https://www.youtube.com/embed/eZ9FpG8May8?feature=oembed&amp;enablejsapi=1\\\" frameborder=\\\"0\\\" allow=\\\"accelerometer; autoplay; encrypted-media; gyroscope; picture-in-picture\\\" allowfullscreen&gt;&lt;/iframe&gt;"
                                      )
                                    , ( "author_name"
                                      , String "Berlin Functional Programming Group"
                                      )
                                    , ( "provider_name" , String "YouTube" )
                                    , ( "thumbnail_url"
                                      , String "https://i.ytimg.com/vi/eZ9FpG8May8/hqdefault.jpg"
                                      )
                                    , ( "thumbnail_height" , Number (360 % 1) )
                                    , ( "author_url"
                                      , String
                                          "https://www.youtube.com/channel/UCNp-DVb8cQRIOo32sZhWgNg"
                                      )
                                    ]
                                )
                              ]
                          )
                        , ( "is_video" , Boolean False )
                        ]
                    )
                  ]
              , Object
                  [ ( "kind" , String "t3" )
                  , ( "data"
                    , Object
                        [ ( "approved_at_utc" , Null )
                        , ( "subreddit" , String "haskell" )
                        , ( "selftext"
                          , String
                              "Saw a thread asking what Haskell is good for. I'm wondering now if it would be more interesting to hear what Haskell isn't good for.\\n\\nBy \\\"bad for\\\" I mean practically speaking given the current availability of ecosystem: libraries, tools, compiler extensions, devs, etc, etc. And, of course, if Haskell isn't good for something theoretically then it won't be good for it practically, so that's interesting too"
                          )
                        , ( "author_fullname" , String "t2_f4gx2" )
                        , ( "saved" , Boolean False )
                        , ( "mod_reason_title" , Null )
                        , ( "gilded" , Number (0 % 1) )
                        , ( "clicked" , Boolean False )
                        , ( "title" , String "What is Haskell bad for?" )
                        , ( "link_flair_richtext" , Array [] )
                        , ( "subreddit_name_prefixed" , String "r/haskell" )
                        , ( "hidden" , Boolean False )
                        , ( "pwls" , Number (6 % 1) )
                        , ( "link_flair_css_class" , Null )
                        , ( "downs" , Number (0 % 1) )
                        , ( "hide_score" , Boolean False )
                        , ( "name" , String "t3_gmxsp4" )
                        , ( "quarantine" , Boolean False )
                        , ( "link_flair_text_color" , String "dark" )
                        , ( "upvote_ratio" , Number (4368491638549381 % 4503599627370496) )
                        , ( "author_flair_background_color" , Null )
                        , ( "subreddit_type" , String "public" )
                        , ( "ups" , Number (27 % 1) )
                        , ( "total_awards_received" , Number (0 % 1) )
                        , ( "media_embed" , Object [] )
                        , ( "author_flair_template_id" , Null )
                        , ( "is_original_content" , Boolean False )
                        , ( "user_reports" , Array [] )
                        , ( "secure_media" , Null )
                        , ( "is_reddit_media_domain" , Boolean False )
                        , ( "is_meta" , Boolean False )
                        , ( "category" , Null )
                        , ( "secure_media_embed" , Object [] )
                        , ( "link_flair_text" , Null )
                        , ( "can_mod_post" , Boolean False )
                        , ( "score" , Number (27 % 1) )
                        , ( "approved_by" , Null )
                        , ( "author_premium" , Boolean False )
                        , ( "thumbnail" , String "" )
                        , ( "edited" , Boolean False )
                        , ( "author_flair_css_class" , Null )
                        , ( "author_flair_richtext" , Array [] )
                        , ( "gildings" , Object [] )
                        , ( "content_categories" , Null )
                        , ( "is_self" , Boolean True )
                        , ( "mod_note" , Null )
                        , ( "created" , Number (1589952776 % 1) )
                        , ( "link_flair_type" , String "text" )
                        , ( "wls" , Number (6 % 1) )
                        , ( "removed_by_category" , Null )
                        , ( "banned_by" , Null )
                        , ( "author_flair_type" , String "text" )
                        , ( "domain" , String "self.haskell" )
                        , ( "allow_live_comments" , Boolean False )
                        , ( "selftext_html"
                          , String
                              "&lt;!-- SC_OFF --&gt;&lt;div class=\\\"md\\\"&gt;&lt;p&gt;Saw a thread asking what Haskell is good for. I&amp;#39;m wondering now if it would be more interesting to hear what Haskell isn&amp;#39;t good for.&lt;/p&gt;\\n\\n&lt;p&gt;By &amp;quot;bad for&amp;quot; I mean practically speaking given the current availability of ecosystem: libraries, tools, compiler extensions, devs, etc, etc. And, of course, if Haskell isn&amp;#39;t good for something theoretically then it won&amp;#39;t be good for it practically, so that&amp;#39;s interesting too&lt;/p&gt;\\n&lt;/div&gt;&lt;!-- SC_ON --&gt;"
                          )
                        , ( "likes" , Null )
                        , ( "suggested_sort" , Null )
                        , ( "banned_at_utc" , Null )
                        , ( "view_count" , Null )
                        , ( "archived" , Boolean False )
                        , ( "no_follow" , Boolean False )
                        , ( "is_crosspostable" , Boolean False )
                        , ( "pinned" , Boolean False )
                        , ( "over_18" , Boolean False )
                        , ( "all_awardings" , Array [] )
                        , ( "awarders" , Array [] )
                        , ( "media_only" , Boolean False )
                        , ( "can_gild" , Boolean False )
                        , ( "spoiler" , Boolean False )
                        , ( "locked" , Boolean False )
                        , ( "author_flair_text" , Null )
                        , ( "treatment_tags" , Array [] )
                        , ( "visited" , Boolean False )
                        , ( "removed_by" , Null )
                        , ( "num_reports" , Null )
                        , ( "distinguished" , Null )
                        , ( "subreddit_id" , String "t5_2qh36" )
                        , ( "mod_reason_by" , Null )
                        , ( "removal_reason" , Null )
                        , ( "link_flair_background_color" , String "" )
                        , ( "id" , String "gmxsp4" )
                        , ( "is_robot_indexable" , Boolean True )
                        , ( "report_reasons" , Null )
                        , ( "author" , String "Dekans" )
                        , ( "discussion_type" , Null )
                        , ( "num_comments" , Number (65 % 1) )
                        , ( "send_replies" , Boolean True )
                        , ( "whitelist_status" , String "all_ads" )
                        , ( "contest_mode" , Boolean False )
                        , ( "mod_reports" , Array [] )
                        , ( "author_patreon_flair" , Boolean False )
                        , ( "author_flair_text_color" , Null )
                        , ( "permalink"
                          , String "/r/haskell/comments/gmxsp4/what_is_haskell_bad_for/"
                          )
                        , ( "parent_whitelist_status" , String "all_ads" )
                        , ( "stickied" , Boolean False )
                        , ( "url"
                          , String
                              "https://old.reddit.com/r/haskell/comments/gmxsp4/what_is_haskell_bad_for/"
                          )
                        , ( "subreddit_subscribers" , Number (55194 % 1) )
                        , ( "created_utc" , Number (1589923976 % 1) )
                        , ( "num_crossposts" , Number (0 % 1) )
                        , ( "media" , Null )
                        , ( "is_video" , Boolean False )
                        ]
                    )
                  ]
              , Object
                  [ ( "kind" , String "t3" )
                  , ( "data"
                    , Object
                        [ ( "approved_at_utc" , Null )
                        , ( "subreddit" , String "haskell" )
                        , ( "selftext" , String "" )
                        , ( "author_fullname" , String "t2_jxviuup" )
                        , ( "saved" , Boolean False )
                        , ( "mod_reason_title" , Null )
                        , ( "gilded" , Number (0 % 1) )
                        , ( "clicked" , Boolean False )
                        , ( "title"
                          , String
                              "Benjamin Pierce: Backtracking Generators for Random Testing"
                          )
                        , ( "link_flair_richtext" , Array [] )
                        , ( "subreddit_name_prefixed" , String "r/haskell" )
                        , ( "hidden" , Boolean False )
                        , ( "pwls" , Number (6 % 1) )
                        , ( "link_flair_css_class" , Null )
                        , ( "downs" , Number (0 % 1) )
                        , ( "hide_score" , Boolean False )
                        , ( "name" , String "t3_gmlw3d" )
                        , ( "quarantine" , Boolean False )
                        , ( "link_flair_text_color" , String "dark" )
                        , ( "upvote_ratio" , Number (8286623314361713 % 9007199254740992) )
                        , ( "author_flair_background_color" , Null )
                        , ( "subreddit_type" , String "public" )
                        , ( "ups" , Number (57 % 1) )
                        , ( "total_awards_received" , Number (0 % 1) )
                        , ( "media_embed" , Object [] )
                        , ( "author_flair_template_id" , Null )
                        , ( "is_original_content" , Boolean False )
                        , ( "user_reports" , Array [] )
                        , ( "secure_media" , Null )
                        , ( "is_reddit_media_domain" , Boolean False )
                        , ( "is_meta" , Boolean False )
                        , ( "category" , Null )
                        , ( "secure_media_embed" , Object [] )
                        , ( "link_flair_text" , Null )
                        , ( "can_mod_post" , Boolean False )
                        , ( "score" , Number (57 % 1) )
                        , ( "approved_by" , Null )
                        , ( "author_premium" , Boolean False )
                        , ( "thumbnail" , String "" )
                        , ( "edited" , Boolean False )
                        , ( "author_flair_css_class" , Null )
                        , ( "author_flair_richtext" , Array [] )
                        , ( "gildings" , Object [] )
                        , ( "content_categories" , Null )
                        , ( "is_self" , Boolean False )
                        , ( "mod_note" , Null )
                        , ( "created" , Number (1589912401 % 1) )
                        , ( "link_flair_type" , String "text" )
                        , ( "wls" , Number (6 % 1) )
                        , ( "removed_by_category" , Null )
                        , ( "banned_by" , Null )
                        , ( "author_flair_type" , String "text" )
                        , ( "domain" , String "youtube.com" )
                        , ( "allow_live_comments" , Boolean False )
                        , ( "selftext_html" , Null )
                        , ( "likes" , Null )
                        , ( "suggested_sort" , Null )
                        , ( "banned_at_utc" , Null )
                        , ( "view_count" , Null )
                        , ( "archived" , Boolean False )
                        , ( "no_follow" , Boolean False )
                        , ( "is_crosspostable" , Boolean False )
                        , ( "pinned" , Boolean False )
                        , ( "over_18" , Boolean False )
                        , ( "all_awardings" , Array [] )
                        , ( "awarders" , Array [] )
                        , ( "media_only" , Boolean False )
                        , ( "can_gild" , Boolean False )
                        , ( "spoiler" , Boolean False )
                        , ( "locked" , Boolean False )
                        , ( "author_flair_text" , Null )
                        , ( "treatment_tags" , Array [] )
                        , ( "visited" , Boolean False )
                        , ( "removed_by" , Null )
                        , ( "num_reports" , Null )
                        , ( "distinguished" , Null )
                        , ( "subreddit_id" , String "t5_2qh36" )
                        , ( "mod_reason_by" , Null )
                        , ( "removal_reason" , Null )
                        , ( "link_flair_background_color" , String "" )
                        , ( "id" , String "gmlw3d" )
                        , ( "is_robot_indexable" , Boolean True )
                        , ( "report_reasons" , Null )
                        , ( "author" , String "iedoub" )
                        , ( "discussion_type" , Null )
                        , ( "num_comments" , Number (2 % 1) )
                        , ( "send_replies" , Boolean True )
                        , ( "whitelist_status" , String "all_ads" )
                        , ( "contest_mode" , Boolean False )
                        , ( "mod_reports" , Array [] )
                        , ( "author_patreon_flair" , Boolean False )
                        , ( "author_flair_text_color" , Null )
                        , ( "permalink"
                          , String
                              "/r/haskell/comments/gmlw3d/benjamin_pierce_backtracking_generators_for/"
                          )
                        , ( "parent_whitelist_status" , String "all_ads" )
                        , ( "stickied" , Boolean False )
                        , ( "url"
                          , String
                              "https://www.youtube.com/watch?v=dfZ94N0hS4I&amp;feature=youtu.be"
                          )
                        , ( "subreddit_subscribers" , Number (55194 % 1) )
                        , ( "created_utc" , Number (1589883601 % 1) )
                        , ( "num_crossposts" , Number (0 % 1) )
                        , ( "media" , Null )
                        , ( "is_video" , Boolean False )
                        ]
                    )
                  ]
              , Object
                  [ ( "kind" , String "t3" )
                  , ( "data"
                    , Object
                        [ ( "approved_at_utc" , Null )
                        , ( "subreddit" , String "haskell" )
                        , ( "selftext" , String "" )
                        , ( "author_fullname" , String "t2_2zl2" )
                        , ( "saved" , Boolean False )
                        , ( "mod_reason_title" , Null )
                        , ( "gilded" , Number (0 % 1) )
                        , ( "clicked" , Boolean False )
                        , ( "title"
                          , String
                              "Haskenthetical - another take on \\\"Haskell with a Lisp syntax\\\""
                          )
                        , ( "link_flair_richtext" , Array [] )
                        , ( "subreddit_name_prefixed" , String "r/haskell" )
                        , ( "hidden" , Boolean False )
                        , ( "pwls" , Number (6 % 1) )
                        , ( "link_flair_css_class" , Null )
                        , ( "downs" , Number (0 % 1) )
                        , ( "hide_score" , Boolean False )
                        , ( "name" , String "t3_gmybcf" )
                        , ( "quarantine" , Boolean False )
                        , ( "link_flair_text_color" , String "dark" )
                        , ( "upvote_ratio" , Number (1 % 1) )
                        , ( "author_flair_background_color" , Null )
                        , ( "subreddit_type" , String "public" )
                        , ( "ups" , Number (5 % 1) )
                        , ( "total_awards_received" , Number (0 % 1) )
                        , ( "media_embed" , Object [] )
                        , ( "author_flair_template_id" , Null )
                        , ( "is_original_content" , Boolean False )
                        , ( "user_reports" , Array [] )
                        , ( "secure_media" , Null )
                        , ( "is_reddit_media_domain" , Boolean False )
                        , ( "is_meta" , Boolean False )
                        , ( "category" , Null )
                        , ( "secure_media_embed" , Object [] )
                        , ( "link_flair_text" , Null )
                        , ( "can_mod_post" , Boolean False )
                        , ( "score" , Number (5 % 1) )
                        , ( "approved_by" , Null )
                        , ( "author_premium" , Boolean False )
                        , ( "thumbnail" , String "" )
                        , ( "edited" , Boolean False )
                        , ( "author_flair_css_class" , Null )
                        , ( "author_flair_richtext" , Array [] )
                        , ( "gildings" , Object [] )
                        , ( "content_categories" , Null )
                        , ( "is_self" , Boolean False )
                        , ( "mod_note" , Null )
                        , ( "created" , Number (1589954453 % 1) )
                        , ( "link_flair_type" , String "text" )
                        , ( "wls" , Number (6 % 1) )
                        , ( "removed_by_category" , Null )
                        , ( "banned_by" , Null )
                        , ( "author_flair_type" , String "text" )
                        , ( "domain" , String "reasonableapproximation.net" )
                        , ( "allow_live_comments" , Boolean False )
                        , ( "selftext_html" , Null )
                        , ( "likes" , Null )
                        , ( "suggested_sort" , Null )
                        , ( "banned_at_utc" , Null )
                        , ( "view_count" , Null )
                        , ( "archived" , Boolean False )
                        , ( "no_follow" , Boolean False )
                        , ( "is_crosspostable" , Boolean False )
                        , ( "pinned" , Boolean False )
                        , ( "over_18" , Boolean False )
                        , ( "all_awardings" , Array [] )
                        , ( "awarders" , Array [] )
                        , ( "media_only" , Boolean False )
                        , ( "can_gild" , Boolean False )
                        , ( "spoiler" , Boolean False )
                        , ( "locked" , Boolean False )
                        , ( "author_flair_text" , Null )
                        , ( "treatment_tags" , Array [] )
                        , ( "visited" , Boolean False )
                        , ( "removed_by" , Null )
                        , ( "num_reports" , Null )
                        , ( "distinguished" , Null )
                        , ( "subreddit_id" , String "t5_2qh36" )
                        , ( "mod_reason_by" , Null )
                        , ( "removal_reason" , Null )
                        , ( "link_flair_background_color" , String "" )
                        , ( "id" , String "gmybcf" )
                        , ( "is_robot_indexable" , Boolean True )
                        , ( "report_reasons" , Null )
                        , ( "author" , String "philh" )
                        , ( "discussion_type" , Null )
                        , ( "num_comments" , Number (2 % 1) )
                        , ( "send_replies" , Boolean True )
                        , ( "whitelist_status" , String "all_ads" )
                        , ( "contest_mode" , Boolean False )
                        , ( "mod_reports" , Array [] )
                        , ( "author_patreon_flair" , Boolean False )
                        , ( "author_flair_text_color" , Null )
                        , ( "permalink"
                          , String
                              "/r/haskell/comments/gmybcf/haskenthetical_another_take_on_haskell_with_a/"
                          )
                        , ( "parent_whitelist_status" , String "all_ads" )
                        , ( "stickied" , Boolean False )
                        , ( "url"
                          , String
                              "http://reasonableapproximation.net/2020/05/19/haskenthetical.html"
                          )
                        , ( "subreddit_subscribers" , Number (55194 % 1) )
                        , ( "created_utc" , Number (1589925653 % 1) )
                        , ( "num_crossposts" , Number (0 % 1) )
                        , ( "media" , Null )
                        , ( "is_video" , Boolean False )
                        ]
                    )
                  ]
              , Object
                  [ ( "kind" , String "t3" )
                  , ( "data"
                    , Object
                        [ ( "approved_at_utc" , Null )
                        , ( "subreddit" , String "haskell" )
                        , ( "selftext" , String "" )
                        , ( "author_fullname" , String "t2_4hurx" )
                        , ( "saved" , Boolean False )
                        , ( "mod_reason_title" , Null )
                        , ( "gilded" , Number (0 % 1) )
                        , ( "clicked" , Boolean False )
                        , ( "title" , String "How to define JSON instances quickly" )
                        , ( "link_flair_richtext" , Array [] )
                        , ( "subreddit_name_prefixed" , String "r/haskell" )
                        , ( "hidden" , Boolean False )
                        , ( "pwls" , Number (6 % 1) )
                        , ( "link_flair_css_class" , Null )
                        , ( "downs" , Number (0 % 1) )
                        , ( "hide_score" , Boolean False )
                        , ( "name" , String "t3_gmmp65" )
                        , ( "quarantine" , Boolean False )
                        , ( "link_flair_text_color" , String "dark" )
                        , ( "upvote_ratio" , Number (8376695306909123 % 9007199254740992) )
                        , ( "author_flair_background_color" , Null )
                        , ( "subreddit_type" , String "public" )
                        , ( "ups" , Number (23 % 1) )
                        , ( "total_awards_received" , Number (0 % 1) )
                        , ( "media_embed" , Object [] )
                        , ( "author_flair_template_id" , Null )
                        , ( "is_original_content" , Boolean False )
                        , ( "user_reports" , Array [] )
                        , ( "secure_media" , Null )
                        , ( "is_reddit_media_domain" , Boolean False )
                        , ( "is_meta" , Boolean False )
                        , ( "category" , Null )
                        , ( "secure_media_embed" , Object [] )
                        , ( "link_flair_text" , Null )
                        , ( "can_mod_post" , Boolean False )
                        , ( "score" , Number (23 % 1) )
                        , ( "approved_by" , Null )
                        , ( "author_premium" , Boolean False )
                        , ( "thumbnail" , String "" )
                        , ( "edited" , Boolean False )
                        , ( "author_flair_css_class" , Null )
                        , ( "author_flair_richtext" , Array [] )
                        , ( "gildings" , Object [] )
                        , ( "content_categories" , Null )
                        , ( "is_self" , Boolean False )
                        , ( "mod_note" , Null )
                        , ( "created" , Number (1589916349 % 1) )
                        , ( "link_flair_type" , String "text" )
                        , ( "wls" , Number (6 % 1) )
                        , ( "removed_by_category" , Null )
                        , ( "banned_by" , Null )
                        , ( "author_flair_type" , String "text" )
                        , ( "domain" , String "dev.to" )
                        , ( "allow_live_comments" , Boolean False )
                        , ( "selftext_html" , Null )
                        , ( "likes" , Null )
                        , ( "suggested_sort" , Null )
                        , ( "banned_at_utc" , Null )
                        , ( "view_count" , Null )
                        , ( "archived" , Boolean False )
                        , ( "no_follow" , Boolean False )
                        , ( "is_crosspostable" , Boolean False )
                        , ( "pinned" , Boolean False )
                        , ( "over_18" , Boolean False )
                        , ( "all_awardings" , Array [] )
                        , ( "awarders" , Array [] )
                        , ( "media_only" , Boolean False )
                        , ( "can_gild" , Boolean False )
                        , ( "spoiler" , Boolean False )
                        , ( "locked" , Boolean False )
                        , ( "author_flair_text" , Null )
                        , ( "treatment_tags" , Array [] )
                        , ( "visited" , Boolean False )
                        , ( "removed_by" , Null )
                        , ( "num_reports" , Null )
                        , ( "distinguished" , Null )
                        , ( "subreddit_id" , String "t5_2qh36" )
                        , ( "mod_reason_by" , Null )
                        , ( "removal_reason" , Null )
                        , ( "link_flair_background_color" , String "" )
                        , ( "id" , String "gmmp65" )
                        , ( "is_robot_indexable" , Boolean True )
                        , ( "report_reasons" , Null )
                        , ( "author" , String "taylorfausak" )
                        , ( "discussion_type" , Null )
                        , ( "num_comments" , Number (9 % 1) )
                        , ( "send_replies" , Boolean True )
                        , ( "whitelist_status" , String "all_ads" )
                        , ( "contest_mode" , Boolean False )
                        , ( "mod_reports" , Array [] )
                        , ( "author_patreon_flair" , Boolean False )
                        , ( "author_flair_text_color" , Null )
                        , ( "permalink"
                          , String
                              "/r/haskell/comments/gmmp65/how_to_define_json_instances_quickly/"
                          )
                        , ( "parent_whitelist_status" , String "all_ads" )
                        , ( "stickied" , Boolean False )
                        , ( "url"
                          , String
                              "https://dev.to/tfausak/how-to-define-json-instances-quickly-5ei7"
                          )
                        , ( "subreddit_subscribers" , Number (55194 % 1) )
                        , ( "created_utc" , Number (1589887549 % 1) )
                        , ( "num_crossposts" , Number (0 % 1) )
                        , ( "media" , Null )
                        , ( "is_video" , Boolean False )
                        ]
                    )
                  ]
              , Object
                  [ ( "kind" , String "t3" )
                  , ( "data"
                    , Object
                        [ ( "approved_at_utc" , Null )
                        , ( "subreddit" , String "haskell" )
                        , ( "selftext"
                          , String
                              "I try to manage my packages by nix, but the following command `nix-env -iA nixpkgs.stack` do not create a `.stack` folder for me, and then run stack global will throw exception like this.\\n\\n```shell\\n$ stack ghci  \\nopenAnonymousTempFileFromDir: inappropriate type (Is a directory)\\n```"
                          )
                        , ( "author_fullname" , String "t2_22yozddx" )
                        , ( "saved" , Boolean False )
                        , ( "mod_reason_title" , Null )
                        , ( "gilded" , Number (0 % 1) )
                        , ( "clicked" , Boolean False )
                        , ( "title"
                          , String
                              "Stack installed by nix seems do not create `.stack` folder under home dir properly."
                          )
                        , ( "link_flair_richtext" , Array [] )
                        , ( "subreddit_name_prefixed" , String "r/haskell" )
                        , ( "hidden" , Boolean False )
                        , ( "pwls" , Number (6 % 1) )
                        , ( "link_flair_css_class" , Null )
                        , ( "downs" , Number (0 % 1) )
                        , ( "hide_score" , Boolean False )
                        , ( "name" , String "t3_gn3vhr" )
                        , ( "quarantine" , Boolean False )
                        , ( "link_flair_text_color" , String "dark" )
                        , ( "upvote_ratio" , Number (1 % 2) )
                        , ( "author_flair_background_color" , Null )
                        , ( "subreddit_type" , String "public" )
                        , ( "ups" , Number (0 % 1) )
                        , ( "total_awards_received" , Number (0 % 1) )
                        , ( "media_embed" , Object [] )
                        , ( "author_flair_template_id" , Null )
                        , ( "is_original_content" , Boolean False )
                        , ( "user_reports" , Array [] )
                        , ( "secure_media" , Null )
                        , ( "is_reddit_media_domain" , Boolean False )
                        , ( "is_meta" , Boolean False )
                        , ( "category" , Null )
                        , ( "secure_media_embed" , Object [] )
                        , ( "link_flair_text" , Null )
                        , ( "can_mod_post" , Boolean False )
                        , ( "score" , Number (0 % 1) )
                        , ( "approved_by" , Null )
                        , ( "author_premium" , Boolean False )
                        , ( "thumbnail" , String "" )
                        , ( "edited" , Boolean False )
                        , ( "author_flair_css_class" , Null )
                        , ( "author_flair_richtext" , Array [] )
                        , ( "gildings" , Object [] )
                        , ( "content_categories" , Null )
                        , ( "is_self" , Boolean True )
                        , ( "mod_note" , Null )
                        , ( "created" , Number (1589974381 % 1) )
                        , ( "link_flair_type" , String "text" )
                        , ( "wls" , Number (6 % 1) )
                        , ( "removed_by_category" , Null )
                        , ( "banned_by" , Null )
                        , ( "author_flair_type" , String "text" )
                        , ( "domain" , String "self.haskell" )
                        , ( "allow_live_comments" , Boolean False )
                        , ( "selftext_html"
                          , String
                              "&lt;!-- SC_OFF --&gt;&lt;div class=\\\"md\\\"&gt;&lt;p&gt;I try to manage my packages by nix, but the following command &lt;code&gt;nix-env -iA nixpkgs.stack&lt;/code&gt; do not create a &lt;code&gt;.stack&lt;/code&gt; folder for me, and then run stack global will throw exception like this.&lt;/p&gt;\\n\\n&lt;p&gt;&lt;code&gt;shell\\n$ stack ghci  \\nopenAnonymousTempFileFromDir: inappropriate type (Is a directory)\\n&lt;/code&gt;&lt;/p&gt;\\n&lt;/div&gt;&lt;!-- SC_ON --&gt;"
                          )
                        , ( "likes" , Null )
                        , ( "suggested_sort" , Null )
                        , ( "banned_at_utc" , Null )
                        , ( "view_count" , Null )
                        , ( "archived" , Boolean False )
                        , ( "no_follow" , Boolean True )
                        , ( "is_crosspostable" , Boolean False )
                        , ( "pinned" , Boolean False )
                        , ( "over_18" , Boolean False )
                        , ( "all_awardings" , Array [] )
                        , ( "awarders" , Array [] )
                        , ( "media_only" , Boolean False )
                        , ( "can_gild" , Boolean False )
                        , ( "spoiler" , Boolean False )
                        , ( "locked" , Boolean False )
                        , ( "author_flair_text" , Null )
                        , ( "treatment_tags" , Array [] )
                        , ( "visited" , Boolean False )
                        , ( "removed_by" , Null )
                        , ( "num_reports" , Null )
                        , ( "distinguished" , Null )
                        , ( "subreddit_id" , String "t5_2qh36" )
                        , ( "mod_reason_by" , Null )
                        , ( "removal_reason" , Null )
                        , ( "link_flair_background_color" , String "" )
                        , ( "id" , String "gn3vhr" )
                        , ( "is_robot_indexable" , Boolean True )
                        , ( "report_reasons" , Null )
                        , ( "author" , String "wangqiao11" )
                        , ( "discussion_type" , Null )
                        , ( "num_comments" , Number (3 % 1) )
                        , ( "send_replies" , Boolean True )
                        , ( "whitelist_status" , String "all_ads" )
                        , ( "contest_mode" , Boolean False )
                        , ( "mod_reports" , Array [] )
                        , ( "author_patreon_flair" , Boolean False )
                        , ( "author_flair_text_color" , Null )
                        , ( "permalink"
                          , String
                              "/r/haskell/comments/gn3vhr/stack_installed_by_nix_seems_do_not_create_stack/"
                          )
                        , ( "parent_whitelist_status" , String "all_ads" )
                        , ( "stickied" , Boolean False )
                        , ( "url"
                          , String
                              "https://old.reddit.com/r/haskell/comments/gn3vhr/stack_installed_by_nix_seems_do_not_create_stack/"
                          )
                        , ( "subreddit_subscribers" , Number (55194 % 1) )
                        , ( "created_utc" , Number (1589945581 % 1) )
                        , ( "num_crossposts" , Number (0 % 1) )
                        , ( "media" , Null )
                        , ( "is_video" , Boolean False )
                        ]
                    )
                  ]
              , Object
                  [ ( "kind" , String "t3" )
                  , ( "data"
                    , Object
                        [ ( "approved_at_utc" , Null )
                        , ( "subreddit" , String "haskell" )
                        , ( "selftext"
                          , String
                              "I've been beating my head against this issue for a while and thought maybe someone here has a good idea of how to approach this problem.   \\nI'm working on a program which has a simple terminal GUI interface using [brick](https://github.com/jtdaugherty/brick), and now I want to be able to run SMT queries in the program using the [SBV](https://hackage.haskell.org/package/sbv-8.6) library. The problem is that the interaction between the program and the SMT solver is being tracked in a monad context (\\\\`[MonadQuery](https://hackage.haskell.org/package/sbv-8.6/docs/src/Data.SBV.Core.Symbolic.html#MonadQuery)\\\\`, \\\\`Query a\\\\` or \\\\`Symbolic a\\\\`), while the event handling monad \\\\`[EventM n a](https://github.com/jtdaugherty/brick/blob/758d8138301ce521214247bd9190abbff7ec0f3d/src/Brick/Types.hs#L128)\\\\` of brick seems to only allow IO actions.  \\n\\n\\nHow would I best go about unifying these contexts? Is there a way to generalize the event handling of brick to allow for other types of monadic actions to be performed? Or should I rather try to save the state that defines the \\\\`MonadQuery\\\\` of SBV in the application state? I found no good way of \\\"saving\\\" the context of a MonadQuery to be able to \\\"resume\\\" it a later time."
                          )
                        , ( "author_fullname" , String "t2_cx67k" )
                        , ( "saved" , Boolean False )
                        , ( "mod_reason_title" , Null )
                        , ( "gilded" , Number (0 % 1) )
                        , ( "clicked" , Boolean False )
                        , ( "title" , String "Combining Brick and SBV monadic contexts" )
                        , ( "link_flair_richtext" , Array [] )
                        , ( "subreddit_name_prefixed" , String "r/haskell" )
                        , ( "hidden" , Boolean False )
                        , ( "pwls" , Number (6 % 1) )
                        , ( "link_flair_css_class" , Null )
                        , ( "downs" , Number (0 % 1) )
                        , ( "hide_score" , Boolean False )
                        , ( "name" , String "t3_gmn78x" )
                        , ( "quarantine" , Boolean False )
                        , ( "link_flair_text_color" , String "dark" )
                        , ( "upvote_ratio" , Number (8286623314361713 % 9007199254740992) )
                        , ( "author_flair_background_color" , Null )
                        , ( "subreddit_type" , String "public" )
                        , ( "ups" , Number (9 % 1) )
                        , ( "total_awards_received" , Number (0 % 1) )
                        , ( "media_embed" , Object [] )
                        , ( "author_flair_template_id" , Null )
                        , ( "is_original_content" , Boolean False )
                        , ( "user_reports" , Array [] )
                        , ( "secure_media" , Null )
                        , ( "is_reddit_media_domain" , Boolean False )
                        , ( "is_meta" , Boolean False )
                        , ( "category" , Null )
                        , ( "secure_media_embed" , Object [] )
                        , ( "link_flair_text" , Null )
                        , ( "can_mod_post" , Boolean False )
                        , ( "score" , Number (9 % 1) )
                        , ( "approved_by" , Null )
                        , ( "author_premium" , Boolean False )
                        , ( "thumbnail" , String "" )
                        , ( "edited" , Boolean False )
                        , ( "author_flair_css_class" , Null )
                        , ( "author_flair_richtext" , Array [] )
                        , ( "gildings" , Object [] )
                        , ( "content_categories" , Null )
                        , ( "is_self" , Boolean True )
                        , ( "mod_note" , Null )
                        , ( "created" , Number (1589918474 % 1) )
                        , ( "link_flair_type" , String "text" )
                        , ( "wls" , Number (6 % 1) )
                        , ( "removed_by_category" , Null )
                        , ( "banned_by" , Null )
                        , ( "author_flair_type" , String "text" )
                        , ( "domain" , String "self.haskell" )
                        , ( "allow_live_comments" , Boolean False )
                        , ( "selftext_html"
                          , String
                              "&lt;!-- SC_OFF --&gt;&lt;div class=\\\"md\\\"&gt;&lt;p&gt;I&amp;#39;ve been beating my head against this issue for a while and thought maybe someone here has a good idea of how to approach this problem.&lt;br/&gt;\\nI&amp;#39;m working on a program which has a simple terminal GUI interface using &lt;a href=\\\"https://github.com/jtdaugherty/brick\\\"&gt;brick&lt;/a&gt;, and now I want to be able to run SMT queries in the program using the &lt;a href=\\\"https://hackage.haskell.org/package/sbv-8.6\\\"&gt;SBV&lt;/a&gt; library. The problem is that the interaction between the program and the SMT solver is being tracked in a monad context (`&lt;a href=\\\"https://hackage.haskell.org/package/sbv-8.6/docs/src/Data.SBV.Core.Symbolic.html#MonadQuery\\\"&gt;MonadQuery&lt;/a&gt;`, `Query a` or `Symbolic a`), while the event handling monad `&lt;a href=\\\"https://github.com/jtdaugherty/brick/blob/758d8138301ce521214247bd9190abbff7ec0f3d/src/Brick/Types.hs#L128\\\"&gt;EventM n a&lt;/a&gt;` of brick seems to only allow IO actions.  &lt;/p&gt;\\n\\n&lt;p&gt;How would I best go about unifying these contexts? Is there a way to generalize the event handling of brick to allow for other types of monadic actions to be performed? Or should I rather try to save the state that defines the `MonadQuery` of SBV in the application state? I found no good way of &amp;quot;saving&amp;quot; the context of a MonadQuery to be able to &amp;quot;resume&amp;quot; it a later time.&lt;/p&gt;\\n&lt;/div&gt;&lt;!-- SC_ON --&gt;"
                          )
                        , ( "likes" , Null )
                        , ( "suggested_sort" , Null )
                        , ( "banned_at_utc" , Null )
                        , ( "view_count" , Null )
                        , ( "archived" , Boolean False )
                        , ( "no_follow" , Boolean False )
                        , ( "is_crosspostable" , Boolean False )
                        , ( "pinned" , Boolean False )
                        , ( "over_18" , Boolean False )
                        , ( "all_awardings" , Array [] )
                        , ( "awarders" , Array [] )
                        , ( "media_only" , Boolean False )
                        , ( "can_gild" , Boolean False )
                        , ( "spoiler" , Boolean False )
                        , ( "locked" , Boolean False )
                        , ( "author_flair_text" , Null )
                        , ( "treatment_tags" , Array [] )
                        , ( "visited" , Boolean False )
                        , ( "removed_by" , Null )
                        , ( "num_reports" , Null )
                        , ( "distinguished" , Null )
                        , ( "subreddit_id" , String "t5_2qh36" )
                        , ( "mod_reason_by" , Null )
                        , ( "removal_reason" , Null )
                        , ( "link_flair_background_color" , String "" )
                        , ( "id" , String "gmn78x" )
                        , ( "is_robot_indexable" , Boolean True )
                        , ( "report_reasons" , Null )
                        , ( "author" , String "Scentable" )
                        , ( "discussion_type" , Null )
                        , ( "num_comments" , Number (5 % 1) )
                        , ( "send_replies" , Boolean True )
                        , ( "whitelist_status" , String "all_ads" )
                        , ( "contest_mode" , Boolean False )
                        , ( "mod_reports" , Array [] )
                        , ( "author_patreon_flair" , Boolean False )
                        , ( "author_flair_text_color" , Null )
                        , ( "permalink"
                          , String
                              "/r/haskell/comments/gmn78x/combining_brick_and_sbv_monadic_contexts/"
                          )
                        , ( "parent_whitelist_status" , String "all_ads" )
                        , ( "stickied" , Boolean False )
                        , ( "url"
                          , String
                              "https://old.reddit.com/r/haskell/comments/gmn78x/combining_brick_and_sbv_monadic_contexts/"
                          )
                        , ( "subreddit_subscribers" , Number (55194 % 1) )
                        , ( "created_utc" , Number (1589889674 % 1) )
                        , ( "num_crossposts" , Number (0 % 1) )
                        , ( "media" , Null )
                        , ( "is_video" , Boolean False )
                        ]
                    )
                  ]
              , Object
                  [ ( "kind" , String "t3" )
                  , ( "data"
                    , Object
                        [ ( "approved_at_utc" , Null )
                        , ( "subreddit" , String "haskell" )
                        , ( "selftext" , String "" )
                        , ( "author_fullname" , String "t2_fr9sxjo" )
                        , ( "saved" , Boolean False )
                        , ( "mod_reason_title" , Null )
                        , ( "gilded" , Number (0 % 1) )
                        , ( "clicked" , Boolean False )
                        , ( "title"
                          , String "I am having difficulty installing Haskero for VSCode"
                          )
                        , ( "link_flair_richtext" , Array [] )
                        , ( "subreddit_name_prefixed" , String "r/haskell" )
                        , ( "hidden" , Boolean False )
                        , ( "pwls" , Number (6 % 1) )
                        , ( "link_flair_css_class" , Null )
                        , ( "downs" , Number (0 % 1) )
                        , ( "hide_score" , Boolean False )
                        , ( "name" , String "t3_gmte13" )
                        , ( "quarantine" , Boolean False )
                        , ( "link_flair_text_color" , String "dark" )
                        , ( "upvote_ratio" , Number (6034823500676465 % 9007199254740992) )
                        , ( "author_flair_background_color" , Null )
                        , ( "subreddit_type" , String "public" )
                        , ( "ups" , Number (2 % 1) )
                        , ( "total_awards_received" , Number (0 % 1) )
                        , ( "media_embed" , Object [] )
                        , ( "author_flair_template_id" , Null )
                        , ( "is_original_content" , Boolean False )
                        , ( "user_reports" , Array [] )
                        , ( "secure_media" , Null )
                        , ( "is_reddit_media_domain" , Boolean False )
                        , ( "is_meta" , Boolean False )
                        , ( "category" , Null )
                        , ( "secure_media_embed" , Object [] )
                        , ( "link_flair_text" , Null )
                        , ( "can_mod_post" , Boolean False )
                        , ( "score" , Number (2 % 1) )
                        , ( "approved_by" , Null )
                        , ( "author_premium" , Boolean False )
                        , ( "thumbnail" , String "" )
                        , ( "edited" , Boolean False )
                        , ( "author_flair_css_class" , Null )
                        , ( "author_flair_richtext" , Array [] )
                        , ( "gildings" , Object [] )
                        , ( "content_categories" , Null )
                        , ( "is_self" , Boolean False )
                        , ( "mod_note" , Null )
                        , ( "crosspost_parent_list"
                          , Array
                              [ Object
                                  [ ( "approved_at_utc" , Null )
                                  , ( "subreddit" , String "vscode" )
                                  , ( "selftext"
                                    , String
                                        "I am currently trying to install Haskero for VSCode. I am using [this link](https://gitlab.com/vannnns/haskero/blob/master/client/doc/installation.md) and following the instructions, however I am stuck on step 5. Whenever I type\\n\\n    stack build intero --copy-compiler-tool\\n\\ninto the terminal, I get this error message:\\n\\n    Error: While constructing the build plan, the following exceptions were encountered:\\n    \\n    In the dependencies for intero-0.1.40:\\n        ghc-8.8.3 from stack configuration does not match &gt;=7.8 &amp;&amp; &lt;=8.6.5  (latest matching version is 8.6.5)\\n    needed since intero is a build target.\\n    \\n    Some different approaches to resolving this:\\n    \\n      * Set 'allow-newer: true' in C:\\\\sr\\\\config.yaml to ignore all version constraints and build anyway.\\n    \\n      * Recommended action: try adding the following to your extra-deps in C:\\\\sr\\\\global-project\\\\stack.yaml:\\n    \\n    - ghc-8.6.5@sha256:3591225289bdf8cf8f62b10f2aebc9ea3e25a15294545a5312a419e0317784f9,13976\\n    \\n    Plan construction failed.\\n\\nI do not know how to handle this. Any  suggestions? Thank you in advance."
                                    )
                                  , ( "author_fullname" , String "t2_fr9sxjo" )
                                  , ( "saved" , Boolean False )
                                  , ( "mod_reason_title" , Null )
                                  , ( "gilded" , Number (0 % 1) )
                                  , ( "clicked" , Boolean False )
                                  , ( "title"
                                    , String "I am having difficulty installing Haskero."
                                    )
                                  , ( "link_flair_richtext" , Array [] )
                                  , ( "subreddit_name_prefixed" , String "r/vscode" )
                                  , ( "hidden" , Boolean False )
                                  , ( "pwls" , Number (6 % 1) )
                                  , ( "link_flair_css_class" , Null )
                                  , ( "downs" , Number (0 % 1) )
                                  , ( "hide_score" , Boolean False )
                                  , ( "name" , String "t3_gm53c8" )
                                  , ( "quarantine" , Boolean False )
                                  , ( "link_flair_text_color" , String "dark" )
                                  , ( "upvote_ratio" , Number (3 % 4) )
                                  , ( "author_flair_background_color" , Null )
                                  , ( "subreddit_type" , String "public" )
                                  , ( "ups" , Number (4 % 1) )
                                  , ( "total_awards_received" , Number (0 % 1) )
                                  , ( "media_embed" , Object [] )
                                  , ( "author_flair_template_id" , Null )
                                  , ( "is_original_content" , Boolean True )
                                  , ( "user_reports" , Array [] )
                                  , ( "secure_media" , Null )
                                  , ( "is_reddit_media_domain" , Boolean False )
                                  , ( "is_meta" , Boolean False )
                                  , ( "category" , Null )
                                  , ( "secure_media_embed" , Object [] )
                                  , ( "link_flair_text" , Null )
                                  , ( "can_mod_post" , Boolean False )
                                  , ( "score" , Number (4 % 1) )
                                  , ( "approved_by" , Null )
                                  , ( "author_premium" , Boolean False )
                                  , ( "thumbnail" , String "" )
                                  , ( "edited" , Boolean False )
                                  , ( "author_flair_css_class" , Null )
                                  , ( "author_flair_richtext" , Array [] )
                                  , ( "gildings" , Object [] )
                                  , ( "content_categories" , Null )
                                  , ( "is_self" , Boolean True )
                                  , ( "mod_note" , Null )
                                  , ( "created" , Number (1589849248 % 1) )
                                  , ( "link_flair_type" , String "text" )
                                  , ( "wls" , Number (6 % 1) )
                                  , ( "removed_by_category" , Null )
                                  , ( "banned_by" , Null )
                                  , ( "author_flair_type" , String "text" )
                                  , ( "domain" , String "self.vscode" )
                                  , ( "allow_live_comments" , Boolean False )
                                  , ( "selftext_html"
                                    , String
                                        "&lt;!-- SC_OFF --&gt;&lt;div class=\\\"md\\\"&gt;&lt;p&gt;I am currently trying to install Haskero for VSCode. I am using &lt;a href=\\\"https://gitlab.com/vannnns/haskero/blob/master/client/doc/installation.md\\\"&gt;this link&lt;/a&gt; and following the instructions, however I am stuck on step 5. Whenever I type&lt;/p&gt;\\n\\n&lt;pre&gt;&lt;code&gt;stack build intero --copy-compiler-tool\\n&lt;/code&gt;&lt;/pre&gt;\\n\\n&lt;p&gt;into the terminal, I get this error message:&lt;/p&gt;\\n\\n&lt;pre&gt;&lt;code&gt;Error: While constructing the build plan, the following exceptions were encountered:\\n\\nIn the dependencies for intero-0.1.40:\\n    ghc-8.8.3 from stack configuration does not match &amp;gt;=7.8 &amp;amp;&amp;amp; &amp;lt;=8.6.5  (latest matching version is 8.6.5)\\nneeded since intero is a build target.\\n\\nSome different approaches to resolving this:\\n\\n  * Set &amp;#39;allow-newer: true&amp;#39; in C:\\\\sr\\\\config.yaml to ignore all version constraints and build anyway.\\n\\n  * Recommended action: try adding the following to your extra-deps in C:\\\\sr\\\\global-project\\\\stack.yaml:\\n\\n- ghc-8.6.5@sha256:3591225289bdf8cf8f62b10f2aebc9ea3e25a15294545a5312a419e0317784f9,13976\\n\\nPlan construction failed.\\n&lt;/code&gt;&lt;/pre&gt;\\n\\n&lt;p&gt;I do not know how to handle this. Any  suggestions? Thank you in advance.&lt;/p&gt;\\n&lt;/div&gt;&lt;!-- SC_ON --&gt;"
                                    )
                                  , ( "likes" , Null )
                                  , ( "suggested_sort" , Null )
                                  , ( "banned_at_utc" , Null )
                                  , ( "view_count" , Null )
                                  , ( "archived" , Boolean False )
                                  , ( "no_follow" , Boolean False )
                                  , ( "is_crosspostable" , Boolean False )
                                  , ( "pinned" , Boolean False )
                                  , ( "over_18" , Boolean False )
                                  , ( "all_awardings" , Array [] )
                                  , ( "awarders" , Array [] )
                                  , ( "media_only" , Boolean False )
                                  , ( "can_gild" , Boolean False )
                                  , ( "spoiler" , Boolean False )
                                  , ( "locked" , Boolean False )
                                  , ( "author_flair_text" , Null )
                                  , ( "treatment_tags" , Array [] )
                                  , ( "visited" , Boolean False )
                                  , ( "removed_by" , Null )
                                  , ( "num_reports" , Null )
                                  , ( "distinguished" , Null )
                                  , ( "subreddit_id" , String "t5_381yu" )
                                  , ( "mod_reason_by" , Null )
                                  , ( "removal_reason" , Null )
                                  , ( "link_flair_background_color" , String "" )
                                  , ( "id" , String "gm53c8" )
                                  , ( "is_robot_indexable" , Boolean True )
                                  , ( "report_reasons" , Null )
                                  , ( "author" , String "The-CPMills" )
                                  , ( "discussion_type" , Null )
                                  , ( "num_comments" , Number (0 % 1) )
                                  , ( "send_replies" , Boolean True )
                                  , ( "whitelist_status" , String "all_ads" )
                                  , ( "contest_mode" , Boolean False )
                                  , ( "mod_reports" , Array [] )
                                  , ( "author_patreon_flair" , Boolean False )
                                  , ( "author_flair_text_color" , Null )
                                  , ( "permalink"
                                    , String
                                        "/r/vscode/comments/gm53c8/i_am_having_difficulty_installing_haskero/"
                                    )
                                  , ( "parent_whitelist_status" , String "all_ads" )
                                  , ( "stickied" , Boolean False )
                                  , ( "url"
                                    , String
                                        "https://old.reddit.com/r/vscode/comments/gm53c8/i_am_having_difficulty_installing_haskero/"
                                    )
                                  , ( "subreddit_subscribers" , Number (40653 % 1) )
                                  , ( "created_utc" , Number (1589820448 % 1) )
                                  , ( "num_crossposts" , Number (1 % 1) )
                                  , ( "media" , Null )
                                  , ( "is_video" , Boolean False )
                                  ]
                              ]
                          )
                        , ( "created" , Number (1589939114 % 1) )
                        , ( "link_flair_type" , String "text" )
                        , ( "wls" , Number (6 % 1) )
                        , ( "removed_by_category" , Null )
                        , ( "banned_by" , Null )
                        , ( "author_flair_type" , String "text" )
                        , ( "domain" , String "self.vscode" )
                        , ( "allow_live_comments" , Boolean False )
                        , ( "selftext_html" , Null )
                        , ( "likes" , Null )
                        , ( "suggested_sort" , Null )
                        , ( "banned_at_utc" , Null )
                        , ( "view_count" , Null )
                        , ( "archived" , Boolean False )
                        , ( "no_follow" , Boolean True )
                        , ( "is_crosspostable" , Boolean False )
                        , ( "pinned" , Boolean False )
                        , ( "over_18" , Boolean False )
                        , ( "all_awardings" , Array [] )
                        , ( "awarders" , Array [] )
                        , ( "media_only" , Boolean False )
                        , ( "can_gild" , Boolean False )
                        , ( "spoiler" , Boolean False )
                        , ( "locked" , Boolean False )
                        , ( "author_flair_text" , Null )
                        , ( "treatment_tags" , Array [] )
                        , ( "visited" , Boolean False )
                        , ( "removed_by" , Null )
                        , ( "num_reports" , Null )
                        , ( "distinguished" , Null )
                        , ( "subreddit_id" , String "t5_2qh36" )
                        , ( "mod_reason_by" , Null )
                        , ( "removal_reason" , Null )
                        , ( "link_flair_background_color" , String "" )
                        , ( "id" , String "gmte13" )
                        , ( "is_robot_indexable" , Boolean True )
                        , ( "report_reasons" , Null )
                        , ( "author" , String "The-CPMills" )
                        , ( "discussion_type" , Null )
                        , ( "num_comments" , Number (5 % 1) )
                        , ( "send_replies" , Boolean True )
                        , ( "whitelist_status" , String "all_ads" )
                        , ( "contest_mode" , Boolean False )
                        , ( "mod_reports" , Array [] )
                        , ( "author_patreon_flair" , Boolean False )
                        , ( "crosspost_parent" , String "t3_gm53c8" )
                        , ( "author_flair_text_color" , Null )
                        , ( "permalink"
                          , String
                              "/r/haskell/comments/gmte13/i_am_having_difficulty_installing_haskero_for/"
                          )
                        , ( "parent_whitelist_status" , String "all_ads" )
                        , ( "stickied" , Boolean False )
                        , ( "url"
                          , String
                              "/r/vscode/comments/gm53c8/i_am_having_difficulty_installing_haskero/"
                          )
                        , ( "subreddit_subscribers" , Number (55194 % 1) )
                        , ( "created_utc" , Number (1589910314 % 1) )
                        , ( "num_crossposts" , Number (0 % 1) )
                        , ( "media" , Null )
                        , ( "is_video" , Boolean False )
                        ]
                    )
                  ]
              , Object
                  [ ( "kind" , String "t3" )
                  , ( "data"
                    , Object
                        [ ( "approved_at_utc" , Null )
                        , ( "subreddit" , String "haskell" )
                        , ( "selftext" , String "" )
                        , ( "author_fullname" , String "t2_7d9ta" )
                        , ( "saved" , Boolean False )
                        , ( "mod_reason_title" , Null )
                        , ( "gilded" , Number (0 % 1) )
                        , ( "clicked" , Boolean False )
                        , ( "title" , String "[GHC Blog] The state of GHC on ARM" )
                        , ( "link_flair_richtext" , Array [] )
                        , ( "subreddit_name_prefixed" , String "r/haskell" )
                        , ( "hidden" , Boolean False )
                        , ( "pwls" , Number (6 % 1) )
                        , ( "link_flair_css_class" , Null )
                        , ( "downs" , Number (0 % 1) )
                        , ( "hide_score" , Boolean False )
                        , ( "name" , String "t3_gmbfyr" )
                        , ( "quarantine" , Boolean False )
                        , ( "link_flair_text_color" , String "dark" )
                        , ( "upvote_ratio" , Number (2206763817411543 % 2251799813685248) )
                        , ( "author_flair_background_color" , Null )
                        , ( "subreddit_type" , String "public" )
                        , ( "ups" , Number (77 % 1) )
                        , ( "total_awards_received" , Number (0 % 1) )
                        , ( "media_embed" , Object [] )
                        , ( "author_flair_template_id" , Null )
                        , ( "is_original_content" , Boolean False )
                        , ( "user_reports" , Array [] )
                        , ( "secure_media" , Null )
                        , ( "is_reddit_media_domain" , Boolean False )
                        , ( "is_meta" , Boolean False )
                        , ( "category" , Null )
                        , ( "secure_media_embed" , Object [] )
                        , ( "link_flair_text" , Null )
                        , ( "can_mod_post" , Boolean False )
                        , ( "score" , Number (77 % 1) )
                        , ( "approved_by" , Null )
                        , ( "author_premium" , Boolean False )
                        , ( "thumbnail" , String "" )
                        , ( "edited" , Boolean False )
                        , ( "author_flair_css_class" , Null )
                        , ( "author_flair_richtext" , Array [] )
                        , ( "gildings" , Object [] )
                        , ( "content_categories" , Null )
                        , ( "is_self" , Boolean False )
                        , ( "mod_note" , Null )
                        , ( "created" , Number (1589868527 % 1) )
                        , ( "link_flair_type" , String "text" )
                        , ( "wls" , Number (6 % 1) )
                        , ( "removed_by_category" , Null )
                        , ( "banned_by" , Null )
                        , ( "author_flair_type" , String "text" )
                        , ( "domain" , String "haskell.org" )
                        , ( "allow_live_comments" , Boolean False )
                        , ( "selftext_html" , Null )
                        , ( "likes" , Null )
                        , ( "suggested_sort" , Null )
                        , ( "banned_at_utc" , Null )
                        , ( "view_count" , Null )
                        , ( "archived" , Boolean False )
                        , ( "no_follow" , Boolean False )
                        , ( "is_crosspostable" , Boolean False )
                        , ( "pinned" , Boolean False )
                        , ( "over_18" , Boolean False )
                        , ( "all_awardings" , Array [] )
                        , ( "awarders" , Array [] )
                        , ( "media_only" , Boolean False )
                        , ( "can_gild" , Boolean False )
                        , ( "spoiler" , Boolean False )
                        , ( "locked" , Boolean False )
                        , ( "author_flair_text" , Null )
                        , ( "treatment_tags" , Array [] )
                        , ( "visited" , Boolean False )
                        , ( "removed_by" , Null )
                        , ( "num_reports" , Null )
                        , ( "distinguished" , Null )
                        , ( "subreddit_id" , String "t5_2qh36" )
                        , ( "mod_reason_by" , Null )
                        , ( "removal_reason" , Null )
                        , ( "link_flair_background_color" , String "" )
                        , ( "id" , String "gmbfyr" )
                        , ( "is_robot_indexable" , Boolean True )
                        , ( "report_reasons" , Null )
                        , ( "author" , String "bgamari" )
                        , ( "discussion_type" , Null )
                        , ( "num_comments" , Number (9 % 1) )
                        , ( "send_replies" , Boolean True )
                        , ( "whitelist_status" , String "all_ads" )
                        , ( "contest_mode" , Boolean False )
                        , ( "mod_reports" , Array [] )
                        , ( "author_patreon_flair" , Boolean False )
                        , ( "author_flair_text_color" , Null )
                        , ( "permalink"
                          , String
                              "/r/haskell/comments/gmbfyr/ghc_blog_the_state_of_ghc_on_arm/"
                          )
                        , ( "parent_whitelist_status" , String "all_ads" )
                        , ( "stickied" , Boolean False )
                        , ( "url"
                          , String
                              "https://www.haskell.org/ghc/blog/20200515-ghc-on-arm.html"
                          )
                        , ( "subreddit_subscribers" , Number (55194 % 1) )
                        , ( "created_utc" , Number (1589839727 % 1) )
                        , ( "num_crossposts" , Number (1 % 1) )
                        , ( "media" , Null )
                        , ( "is_video" , Boolean False )
                        ]
                    )
                  ]
              , Object
                  [ ( "kind" , String "t3" )
                  , ( "data"
                    , Object
                        [ ( "approved_at_utc" , Null )
                        , ( "subreddit" , String "haskell" )
                        , ( "selftext"
                          , String
                              "I'm trying to build the board for the Peg Solitaire game but I'm stuck. I hope you can help me. The following code runs and generates a square of 3 on 3 circles. How could I make 3 more such squares but put them in other positions? I use the Gloss library. \\n\\n&amp;#x200B;\\n\\n`module Main(main) where` \\n\\n`import Graphics.Gloss` \\n\\n`import Graphics.Gloss.Data.ViewPort` \\n\\n`import` [`Graphics.Gloss.Interface.Pure.Game`](https://Graphics.Gloss.Interface.Pure.Game)\\n\\n `import Data.List`  \\n\\n`width, height, offset :: Int` \\n\\n`width = 400` \\n\\n`height = 400`\\n\\n `offset = 100`  \\n\\n`window :: Display window = InWindow \\\"Peg Solitaire\\\" (width, height) (offset, offset)`\\n\\n  `background :: Color` \\n\\n`background = white`  \\n\\n`drawing :: Picture` \\n\\n`drawing = Pictures [ (translate (x * 40) (y * 40) $ circleSolid 12)| x&lt;-[-1..1], y&lt;-[2..4] ]`  \\n\\n`main = display window background drawing`"
                          )
                        , ( "author_fullname" , String "t2_tewbqxp" )
                        , ( "saved" , Boolean False )
                        , ( "mod_reason_title" , Null )
                        , ( "gilded" , Number (0 % 1) )
                        , ( "clicked" , Boolean False )
                        , ( "title" , String "Drawing the game board in Haskell" )
                        , ( "link_flair_richtext" , Array [] )
                        , ( "subreddit_name_prefixed" , String "r/haskell" )
                        , ( "hidden" , Boolean False )
                        , ( "pwls" , Number (6 % 1) )
                        , ( "link_flair_css_class" , Null )
                        , ( "downs" , Number (0 % 1) )
                        , ( "hide_score" , Boolean False )
                        , ( "name" , String "t3_gmsipz" )
                        , ( "quarantine" , Boolean False )
                        , ( "link_flair_text_color" , String "dark" )
                        , ( "upvote_ratio" , Number (3 % 4) )
                        , ( "author_flair_background_color" , Null )
                        , ( "subreddit_type" , String "public" )
                        , ( "ups" , Number (4 % 1) )
                        , ( "total_awards_received" , Number (0 % 1) )
                        , ( "media_embed" , Object [] )
                        , ( "author_flair_template_id" , Null )
                        , ( "is_original_content" , Boolean False )
                        , ( "user_reports" , Array [] )
                        , ( "secure_media" , Null )
                        , ( "is_reddit_media_domain" , Boolean False )
                        , ( "is_meta" , Boolean False )
                        , ( "category" , Null )
                        , ( "secure_media_embed" , Object [] )
                        , ( "link_flair_text" , Null )
                        , ( "can_mod_post" , Boolean False )
                        , ( "score" , Number (4 % 1) )
                        , ( "approved_by" , Null )
                        , ( "author_premium" , Boolean False )
                        , ( "thumbnail" , String "" )
                        , ( "edited" , Boolean False )
                        , ( "author_flair_css_class" , Null )
                        , ( "author_flair_richtext" , Array [] )
                        , ( "gildings" , Object [] )
                        , ( "content_categories" , Null )
                        , ( "is_self" , Boolean True )
                        , ( "mod_note" , Null )
                        , ( "created" , Number (1589936485 % 1) )
                        , ( "link_flair_type" , String "text" )
                        , ( "wls" , Number (6 % 1) )
                        , ( "removed_by_category" , Null )
                        , ( "banned_by" , Null )
                        , ( "author_flair_type" , String "text" )
                        , ( "domain" , String "self.haskell" )
                        , ( "allow_live_comments" , Boolean False )
                        , ( "selftext_html"
                          , String
                              "&lt;!-- SC_OFF --&gt;&lt;div class=\\\"md\\\"&gt;&lt;p&gt;I&amp;#39;m trying to build the board for the Peg Solitaire game but I&amp;#39;m stuck. I hope you can help me. The following code runs and generates a square of 3 on 3 circles. How could I make 3 more such squares but put them in other positions? I use the Gloss library. &lt;/p&gt;\\n\\n&lt;p&gt;&amp;#x200B;&lt;/p&gt;\\n\\n&lt;p&gt;&lt;code&gt;module Main(main) where&lt;/code&gt; &lt;/p&gt;\\n\\n&lt;p&gt;&lt;code&gt;import Graphics.Gloss&lt;/code&gt; &lt;/p&gt;\\n\\n&lt;p&gt;&lt;code&gt;import Graphics.Gloss.Data.ViewPort&lt;/code&gt; &lt;/p&gt;\\n\\n&lt;p&gt;&lt;code&gt;import&lt;/code&gt; &lt;a href=\\\"https://Graphics.Gloss.Interface.Pure.Game\\\"&gt;&lt;code&gt;Graphics.Gloss.Interface.Pure.Game&lt;/code&gt;&lt;/a&gt;&lt;/p&gt;\\n\\n&lt;p&gt;&lt;code&gt;import Data.List&lt;/code&gt;  &lt;/p&gt;\\n\\n&lt;p&gt;&lt;code&gt;width, height, offset :: Int&lt;/code&gt; &lt;/p&gt;\\n\\n&lt;p&gt;&lt;code&gt;width = 400&lt;/code&gt; &lt;/p&gt;\\n\\n&lt;p&gt;&lt;code&gt;height = 400&lt;/code&gt;&lt;/p&gt;\\n\\n&lt;p&gt;&lt;code&gt;offset = 100&lt;/code&gt;  &lt;/p&gt;\\n\\n&lt;p&gt;&lt;code&gt;window :: Display window = InWindow &amp;quot;Peg Solitaire&amp;quot; (width, height) (offset, offset)&lt;/code&gt;&lt;/p&gt;\\n\\n&lt;p&gt;&lt;code&gt;background :: Color&lt;/code&gt; &lt;/p&gt;\\n\\n&lt;p&gt;&lt;code&gt;background = white&lt;/code&gt;  &lt;/p&gt;\\n\\n&lt;p&gt;&lt;code&gt;drawing :: Picture&lt;/code&gt; &lt;/p&gt;\\n\\n&lt;p&gt;&lt;code&gt;drawing = Pictures [ (translate (x * 40) (y * 40) $ circleSolid 12)| x&amp;lt;-[-1..1], y&amp;lt;-[2..4] ]&lt;/code&gt;  &lt;/p&gt;\\n\\n&lt;p&gt;&lt;code&gt;main = display window background drawing&lt;/code&gt;&lt;/p&gt;\\n&lt;/div&gt;&lt;!-- SC_ON --&gt;"
                          )
                        , ( "likes" , Null )
                        , ( "suggested_sort" , Null )
                        , ( "banned_at_utc" , Null )
                        , ( "view_count" , Null )
                        , ( "archived" , Boolean False )
                        , ( "no_follow" , Boolean True )
                        , ( "is_crosspostable" , Boolean False )
                        , ( "pinned" , Boolean False )
                        , ( "over_18" , Boolean False )
                        , ( "all_awardings" , Array [] )
                        , ( "awarders" , Array [] )
                        , ( "media_only" , Boolean False )
                        , ( "can_gild" , Boolean False )
                        , ( "spoiler" , Boolean False )
                        , ( "locked" , Boolean False )
                        , ( "author_flair_text" , Null )
                        , ( "treatment_tags" , Array [] )
                        , ( "visited" , Boolean False )
                        , ( "removed_by" , Null )
                        , ( "num_reports" , Null )
                        , ( "distinguished" , Null )
                        , ( "subreddit_id" , String "t5_2qh36" )
                        , ( "mod_reason_by" , Null )
                        , ( "removal_reason" , Null )
                        , ( "link_flair_background_color" , String "" )
                        , ( "id" , String "gmsipz" )
                        , ( "is_robot_indexable" , Boolean True )
                        , ( "report_reasons" , Null )
                        , ( "author" , String "radu23" )
                        , ( "discussion_type" , Null )
                        , ( "num_comments" , Number (11 % 1) )
                        , ( "send_replies" , Boolean True )
                        , ( "whitelist_status" , String "all_ads" )
                        , ( "contest_mode" , Boolean False )
                        , ( "mod_reports" , Array [] )
                        , ( "author_patreon_flair" , Boolean False )
                        , ( "author_flair_text_color" , Null )
                        , ( "permalink"
                          , String
                              "/r/haskell/comments/gmsipz/drawing_the_game_board_in_haskell/"
                          )
                        , ( "parent_whitelist_status" , String "all_ads" )
                        , ( "stickied" , Boolean False )
                        , ( "url"
                          , String
                              "https://old.reddit.com/r/haskell/comments/gmsipz/drawing_the_game_board_in_haskell/"
                          )
                        , ( "subreddit_subscribers" , Number (55194 % 1) )
                        , ( "created_utc" , Number (1589907685 % 1) )
                        , ( "num_crossposts" , Number (0 % 1) )
                        , ( "media" , Null )
                        , ( "is_video" , Boolean False )
                        ]
                    )
                  ]
              , Object
                  [ ( "kind" , String "t3" )
                  , ( "data"
                    , Object
                        [ ( "approved_at_utc" , Null )
                        , ( "subreddit" , String "haskell" )
                        , ( "selftext" , String "" )
                        , ( "author_fullname" , String "t2_jxviuup" )
                        , ( "saved" , Boolean False )
                        , ( "mod_reason_title" , Null )
                        , ( "gilded" , Number (0 % 1) )
                        , ( "clicked" , Boolean False )
                        , ( "title"
                          , String
                              "Presentation on Purely Functional Data Structures - Donnacha Ois\195\173n Kidney"
                          )
                        , ( "link_flair_richtext" , Array [] )
                        , ( "subreddit_name_prefixed" , String "r/haskell" )
                        , ( "hidden" , Boolean False )
                        , ( "pwls" , Number (6 % 1) )
                        , ( "link_flair_css_class" , Null )
                        , ( "downs" , Number (0 % 1) )
                        , ( "hide_score" , Boolean False )
                        , ( "name" , String "t3_gmen1i" )
                        , ( "quarantine" , Boolean False )
                        , ( "link_flair_text_color" , String "dark" )
                        , ( "upvote_ratio" , Number (1 % 1) )
                        , ( "author_flair_background_color" , Null )
                        , ( "subreddit_type" , String "public" )
                        , ( "ups" , Number (27 % 1) )
                        , ( "total_awards_received" , Number (0 % 1) )
                        , ( "media_embed" , Object [] )
                        , ( "author_flair_template_id" , Null )
                        , ( "is_original_content" , Boolean False )
                        , ( "user_reports" , Array [] )
                        , ( "secure_media" , Null )
                        , ( "is_reddit_media_domain" , Boolean False )
                        , ( "is_meta" , Boolean False )
                        , ( "category" , Null )
                        , ( "secure_media_embed" , Object [] )
                        , ( "link_flair_text" , Null )
                        , ( "can_mod_post" , Boolean False )
                        , ( "score" , Number (27 % 1) )
                        , ( "approved_by" , Null )
                        , ( "author_premium" , Boolean False )
                        , ( "thumbnail" , String "" )
                        , ( "edited" , Boolean False )
                        , ( "author_flair_css_class" , Null )
                        , ( "author_flair_richtext" , Array [] )
                        , ( "gildings" , Object [] )
                        , ( "content_categories" , Null )
                        , ( "is_self" , Boolean False )
                        , ( "mod_note" , Null )
                        , ( "created" , Number (1589879479 % 1) )
                        , ( "link_flair_type" , String "text" )
                        , ( "wls" , Number (6 % 1) )
                        , ( "removed_by_category" , Null )
                        , ( "banned_by" , Null )
                        , ( "author_flair_type" , String "text" )
                        , ( "domain" , String "doisinkidney.com" )
                        , ( "allow_live_comments" , Boolean False )
                        , ( "selftext_html" , Null )
                        , ( "likes" , Null )
                        , ( "suggested_sort" , Null )
                        , ( "banned_at_utc" , Null )
                        , ( "view_count" , Null )
                        , ( "archived" , Boolean False )
                        , ( "no_follow" , Boolean False )
                        , ( "is_crosspostable" , Boolean False )
                        , ( "pinned" , Boolean False )
                        , ( "over_18" , Boolean False )
                        , ( "all_awardings" , Array [] )
                        , ( "awarders" , Array [] )
                        , ( "media_only" , Boolean False )
                        , ( "can_gild" , Boolean False )
                        , ( "spoiler" , Boolean False )
                        , ( "locked" , Boolean False )
                        , ( "author_flair_text" , Null )
                        , ( "treatment_tags" , Array [] )
                        , ( "visited" , Boolean False )
                        , ( "removed_by" , Null )
                        , ( "num_reports" , Null )
                        , ( "distinguished" , Null )
                        , ( "subreddit_id" , String "t5_2qh36" )
                        , ( "mod_reason_by" , Null )
                        , ( "removal_reason" , Null )
                        , ( "link_flair_background_color" , String "" )
                        , ( "id" , String "gmen1i" )
                        , ( "is_robot_indexable" , Boolean True )
                        , ( "report_reasons" , Null )
                        , ( "author" , String "iedoub" )
                        , ( "discussion_type" , Null )
                        , ( "num_comments" , Number (12 % 1) )
                        , ( "send_replies" , Boolean True )
                        , ( "whitelist_status" , String "all_ads" )
                        , ( "contest_mode" , Boolean False )
                        , ( "mod_reports" , Array [] )
                        , ( "author_patreon_flair" , Boolean False )
                        , ( "author_flair_text_color" , Null )
                        , ( "permalink"
                          , String
                              "/r/haskell/comments/gmen1i/presentation_on_purely_functional_data_structures/"
                          )
                        , ( "parent_whitelist_status" , String "all_ads" )
                        , ( "stickied" , Boolean False )
                        , ( "url"
                          , String
                              "https://doisinkidney.com/posts/2020-05-19-purely-functional-data-structures-slides.html"
                          )
                        , ( "subreddit_subscribers" , Number (55194 % 1) )
                        , ( "created_utc" , Number (1589850679 % 1) )
                        , ( "num_crossposts" , Number (0 % 1) )
                        , ( "media" , Null )
                        , ( "is_video" , Boolean False )
                        ]
                    )
                  ]
              , Object
                  [ ( "kind" , String "t3" )
                  , ( "data"
                    , Object
                        [ ( "approved_at_utc" , Null )
                        , ( "subreddit" , String "haskell" )
                        , ( "selftext"
                          , String
                              "I created a project with stack. Most of the time during the project I used the .cabal file to add dependencies. And that worked fine. However when adding the dependency for a sat-solver I got the following error\\n\\n```\\nminisat-solver needed, but the stack configuration has no specified version  (latest matching version\\n               is 0.1)\\n```\\n\\nTo solve this error I added the line\\n\\n```\\n - minisat-solver-0.1@sha256:e2ff11b1ca8c66e43f8bb2e04f21bd1b812efb94ff215d74f998c928e7e92dcd,5210\\n```\\n\\nto my .yaml file.\\n\\nNow whenever I use `stack build` I get the error\\n\\n```\\n....cabal was modified manually Ignoring ...package.yaml in favor of the cabal file.\\nIf you want to use the package.yaml file instead of the cabal file,\\nthen please delete the cabal file.\\n```\\n\\nHow should I solve this? Should I just delete the .cabal file? What changes should I make to .yaml file\\n\\n--\\n\\nThe .yaml flie\\n\\n```\\n# This file was automatically generated by 'stack init'\\n#\\n# Some commonly used options have been documented as comments in this file.\\n# For advanced use and comprehensive documentation of the format, please see:\\n# https://docs.haskellstack.org/en/stable/yaml_configuration/\\n\\n# Resolver to choose a 'specific' stackage snapshot or a compiler version.\\n# A snapshot resolver dictates the compiler version and the set of packages\\n# to be used for project dependencies. For example:\\n#\\n# resolver: lts-3.5\\n# resolver: nightly-2015-09-21\\n# resolver: ghc-7.10.2\\n#\\n# The location of a snapshot can be provided as a file or url. Stack assumes\\n# a snapshot provided as a file might change, whereas a url resource does not.\\n#\\n# resolver: ./custom-snapshot.yaml\\n# resolver: https://example.com/snapshots/2018-01-01.yaml\\nresolver: lts-14.20\\n\\n# User packages to be built.\\n# Various formats can be used as shown in the example below.\\n#\\n# packages:\\n# - some-directory\\n# - https://example.com/foo/bar/baz-0.0.2.tar.gz\\n#   subdirs:\\n#   - auto-update\\n#   - wai\\npackages:\\n- .\\n# Dependency packages to be pulled from upstream that are not in the resolver.\\n# These entries can reference officially published versions as well as\\n# forks / in-progress versions pinned to a git hash. For example:\\n#\\n# extra-deps:\\n# - acme-missiles-0.3\\n# - git: https://github.com/commercialhaskell/stack.git\\n#   commit: e7b331f14bcffb8367cd58fbfc8b40ec7642100a\\n#\\n# extra-deps: []\\n\\n# Override default flag values for local packages and extra-deps\\n# flags: {}\\n\\n# Extra package databases containing global packages\\n# extra-package-dbs: []\\n\\n# Control whether we use the GHC we find on the path\\n# system-ghc: true\\n#\\n# Require a specific version of stack, using version ranges\\n# require-stack-version: -any # Default\\n# require-stack-version: \\\"&gt;=2.1\\\"\\n#\\n# Override the architecture used by stack, especially useful on Windows\\n# arch: i386\\n# arch: x86_64\\n#\\n# Extra directories used by stack for building\\n# extra-include-dirs: [/path/to/dir]\\n# extra-lib-dirs: [/path/to/dir]\\n#\\n# Allow a newer minor version of GHC than the snapshot specifies\\n# compiler-check: newer-minor\\n\\nextra-deps:\\n - minisat-solver-0.1@sha256:e2ff11b1ca8c66e43f8bb2e04f21bd1b812efb94ff215d74f998c928e7e92dcd,5210\\n\\n```\\n\\nThe cabal file\\n\\n```\\ncabal-version: 1.12\\n\\n-- This file has been generated from package.yaml by hpack version 0.31.2.\\n--\\n-- see: https://github.com/sol/hpack\\n--\\n-- hash: 9e4c1b8d2c640f6364c7abf13e184823a0c4b7959a05310c93a9b6ff92efad16\\n\\nname:           dtl-model-checking\\nversion:        0.1.0.0\\ndescription:    Please see the README on GitHub at &lt;https://github.com/githubuser/dtl-model-checking#readme&gt;\\nhomepage:       https://github.com/githubuser/dtl-model-checking#readme\\nbug-reports:    https://github.com/githubuser/dtl-model-checking/issues\\nauthor:         Author name here\\nmaintainer:     example@example.com\\ncopyright:      2020 Author name here\\nlicense:        BSD3\\nlicense-file:   LICENSE\\nbuild-type:     Simple\\nextra-source-files:\\n    README.md\\n    ChangeLog.md\\n\\nsource-repository head\\n  type: git\\n  location: https://github.com/githubuser/dtl-model-checking\\n\\nlibrary\\n  exposed-modules:\\n      Automaton\\n      DTLFormula\\n      AutomataTheoreticApproach\\n      DTS\\n      NBA\\n      GNBA\\n      Ielementary\\n      CommonTypes\\n      Utils\\n      ExampleInstances\\n      BMC\\n  other-modules:\\n      Paths_dtl_model_checking\\n  hs-source-dirs:\\n      src\\n  build-depends:\\n      base &gt;=4.7 &amp;&amp; &lt;5\\n    , containers\\n    , random\\n    , minisat-solver &gt;= 0.1\\n  default-language: Haskell2010\\n\\nexecutable dtl-model-checking-exe\\n  main-is: Main.hs\\n  other-modules:\\n      Paths_dtl_model_checking\\n  hs-source-dirs:\\n      app\\n  ghc-options: -O -threaded -rtsopts -with-rtsopts=-N\\n  build-depends:\\n      base &gt;=4.7 &amp;&amp; &lt;5\\n    , dtl-model-checking\\n    , containers\\n    , random\\n  default-language: Haskell2010\\n\\ntest-suite dtl-model-checking-test\\n  type: exitcode-stdio-1.0\\n  main-is: Spec.hs\\n  other-modules:\\n      Paths_dtl_model_checking\\n  hs-source-dirs:\\n      test\\n  ghc-options: -O -threaded -rtsopts -with-rtsopts=-N\\n  build-depends:\\n      base &gt;=4.7 &amp;&amp; &lt;5\\n    , dtl-model-checking\\n    , containers\\n    , hspec\\n    , random\\n  default-language: Haskell2010\\n\\nbenchmark dtl-model-checking-benchmark\\n  type: exitcode-stdio-1.0 \\n  main-is: Bench.hs\\n  other-modules:\\n      Paths_dtl_model_checking\\n  hs-source-dirs:\\n      benchmark\\n  ghc-options: -O -threaded -fforce-recomp -rtsopts -with-rtsopts=-N\\n  build-depends: base &gt;=4.7 &amp;&amp; &lt;5, dtl-model-checking, containers, criterion, random\\n  default-language: Haskell2010\\n```"
                          )
                        , ( "author_fullname" , String "t2_u7qgp4w" )
                        , ( "saved" , Boolean False )
                        , ( "mod_reason_title" , Null )
                        , ( "gilded" , Number (0 % 1) )
                        , ( "clicked" , Boolean False )
                        , ( "title" , String "Error/warning on stack build" )
                        , ( "link_flair_richtext" , Array [] )
                        , ( "subreddit_name_prefixed" , String "r/haskell" )
                        , ( "hidden" , Boolean False )
                        , ( "pwls" , Number (6 % 1) )
                        , ( "link_flair_css_class" , Null )
                        , ( "downs" , Number (0 % 1) )
                        , ( "hide_score" , Boolean False )
                        , ( "name" , String "t3_gmoik7" )
                        , ( "quarantine" , Boolean False )
                        , ( "link_flair_text_color" , String "dark" )
                        , ( "upvote_ratio" , Number (1 % 2) )
                        , ( "author_flair_background_color" , Null )
                        , ( "subreddit_type" , String "public" )
                        , ( "ups" , Number (0 % 1) )
                        , ( "total_awards_received" , Number (0 % 1) )
                        , ( "media_embed" , Object [] )
                        , ( "author_flair_template_id" , Null )
                        , ( "is_original_content" , Boolean False )
                        , ( "user_reports" , Array [] )
                        , ( "secure_media" , Null )
                        , ( "is_reddit_media_domain" , Boolean False )
                        , ( "is_meta" , Boolean False )
                        , ( "category" , Null )
                        , ( "secure_media_embed" , Object [] )
                        , ( "link_flair_text" , Null )
                        , ( "can_mod_post" , Boolean False )
                        , ( "score" , Number (0 % 1) )
                        , ( "approved_by" , Null )
                        , ( "author_premium" , Boolean False )
                        , ( "thumbnail" , String "" )
                        , ( "edited" , Boolean False )
                        , ( "author_flair_css_class" , Null )
                        , ( "author_flair_richtext" , Array [] )
                        , ( "gildings" , Object [] )
                        , ( "content_categories" , Null )
                        , ( "is_self" , Boolean True )
                        , ( "mod_note" , Null )
                        , ( "created" , Number (1589923554 % 1) )
                        , ( "link_flair_type" , String "text" )
                        , ( "wls" , Number (6 % 1) )
                        , ( "removed_by_category" , Null )
                        , ( "banned_by" , Null )
                        , ( "author_flair_type" , String "text" )
                        , ( "domain" , String "self.haskell" )
                        , ( "allow_live_comments" , Boolean False )
                        , ( "selftext_html"
                          , String
                              "&lt;!-- SC_OFF --&gt;&lt;div class=\\\"md\\\"&gt;&lt;p&gt;I created a project with stack. Most of the time during the project I used the .cabal file to add dependencies. And that worked fine. However when adding the dependency for a sat-solver I got the following error&lt;/p&gt;\\n\\n&lt;p&gt;&lt;code&gt;\\nminisat-solver needed, but the stack configuration has no specified version  (latest matching version\\n               is 0.1)\\n&lt;/code&gt;&lt;/p&gt;\\n\\n&lt;p&gt;To solve this error I added the line&lt;/p&gt;\\n\\n&lt;p&gt;&lt;code&gt;\\n - minisat-solver-0.1@sha256:e2ff11b1ca8c66e43f8bb2e04f21bd1b812efb94ff215d74f998c928e7e92dcd,5210\\n&lt;/code&gt;&lt;/p&gt;\\n\\n&lt;p&gt;to my .yaml file.&lt;/p&gt;\\n\\n&lt;p&gt;Now whenever I use &lt;code&gt;stack build&lt;/code&gt; I get the error&lt;/p&gt;\\n\\n&lt;p&gt;&lt;code&gt;\\n....cabal was modified manually Ignoring ...package.yaml in favor of the cabal file.\\nIf you want to use the package.yaml file instead of the cabal file,\\nthen please delete the cabal file.\\n&lt;/code&gt;&lt;/p&gt;\\n\\n&lt;p&gt;How should I solve this? Should I just delete the .cabal file? What changes should I make to .yaml file&lt;/p&gt;\\n\\n&lt;h2&gt;&lt;/h2&gt;\\n\\n&lt;p&gt;The .yaml flie&lt;/p&gt;\\n\\n&lt;p&gt;```&lt;/p&gt;\\n\\n&lt;h1&gt;This file was automatically generated by &amp;#39;stack init&amp;#39;&lt;/h1&gt;\\n\\n&lt;h1&gt;Some commonly used options have been documented as comments in this file.&lt;/h1&gt;\\n\\n&lt;h1&gt;For advanced use and comprehensive documentation of the format, please see:&lt;/h1&gt;\\n\\n&lt;h1&gt;&lt;a href=\\\"https://docs.haskellstack.org/en/stable/yaml_configuration/\\\"&gt;https://docs.haskellstack.org/en/stable/yaml_configuration/&lt;/a&gt;&lt;/h1&gt;\\n\\n&lt;h1&gt;Resolver to choose a &amp;#39;specific&amp;#39; stackage snapshot or a compiler version.&lt;/h1&gt;\\n\\n&lt;h1&gt;A snapshot resolver dictates the compiler version and the set of packages&lt;/h1&gt;\\n\\n&lt;h1&gt;to be used for project dependencies. For example:&lt;/h1&gt;\\n\\n&lt;h1&gt;resolver: lts-3.5&lt;/h1&gt;\\n\\n&lt;h1&gt;resolver: nightly-2015-09-21&lt;/h1&gt;\\n\\n&lt;h1&gt;resolver: ghc-7.10.2&lt;/h1&gt;\\n\\n&lt;h1&gt;The location of a snapshot can be provided as a file or url. Stack assumes&lt;/h1&gt;\\n\\n&lt;h1&gt;a snapshot provided as a file might change, whereas a url resource does not.&lt;/h1&gt;\\n\\n&lt;h1&gt;resolver: ./custom-snapshot.yaml&lt;/h1&gt;\\n\\n&lt;h1&gt;resolver: &lt;a href=\\\"https://example.com/snapshots/2018-01-01.yaml\\\"&gt;https://example.com/snapshots/2018-01-01.yaml&lt;/a&gt;&lt;/h1&gt;\\n\\n&lt;p&gt;resolver: lts-14.20&lt;/p&gt;\\n\\n&lt;h1&gt;User packages to be built.&lt;/h1&gt;\\n\\n&lt;h1&gt;Various formats can be used as shown in the example below.&lt;/h1&gt;\\n\\n&lt;h1&gt;packages:&lt;/h1&gt;\\n\\n&lt;h1&gt;- some-directory&lt;/h1&gt;\\n\\n&lt;h1&gt;- &lt;a href=\\\"https://example.com/foo/bar/baz-0.0.2.tar.gz\\\"&gt;https://example.com/foo/bar/baz-0.0.2.tar.gz&lt;/a&gt;&lt;/h1&gt;\\n\\n&lt;h1&gt;subdirs:&lt;/h1&gt;\\n\\n&lt;h1&gt;- auto-update&lt;/h1&gt;\\n\\n&lt;h1&gt;- wai&lt;/h1&gt;\\n\\n&lt;p&gt;packages:\\n- .&lt;/p&gt;\\n\\n&lt;h1&gt;Dependency packages to be pulled from upstream that are not in the resolver.&lt;/h1&gt;\\n\\n&lt;h1&gt;These entries can reference officially published versions as well as&lt;/h1&gt;\\n\\n&lt;h1&gt;forks / in-progress versions pinned to a git hash. For example:&lt;/h1&gt;\\n\\n&lt;h1&gt;extra-deps:&lt;/h1&gt;\\n\\n&lt;h1&gt;- acme-missiles-0.3&lt;/h1&gt;\\n\\n&lt;h1&gt;- git: &lt;a href=\\\"https://github.com/commercialhaskell/stack.git\\\"&gt;https://github.com/commercialhaskell/stack.git&lt;/a&gt;&lt;/h1&gt;\\n\\n&lt;h1&gt;commit: e7b331f14bcffb8367cd58fbfc8b40ec7642100a&lt;/h1&gt;\\n\\n&lt;h1&gt;extra-deps: []&lt;/h1&gt;\\n\\n&lt;h1&gt;Override default flag values for local packages and extra-deps&lt;/h1&gt;\\n\\n&lt;h1&gt;flags: {}&lt;/h1&gt;\\n\\n&lt;h1&gt;Extra package databases containing global packages&lt;/h1&gt;\\n\\n&lt;h1&gt;extra-package-dbs: []&lt;/h1&gt;\\n\\n&lt;h1&gt;Control whether we use the GHC we find on the path&lt;/h1&gt;\\n\\n&lt;h1&gt;system-ghc: true&lt;/h1&gt;\\n\\n&lt;h1&gt;Require a specific version of stack, using version ranges&lt;/h1&gt;\\n\\n&lt;h1&gt;require-stack-version: -any # Default&lt;/h1&gt;\\n\\n&lt;h1&gt;require-stack-version: &amp;quot;&amp;gt;=2.1&amp;quot;&lt;/h1&gt;\\n\\n&lt;h1&gt;Override the architecture used by stack, especially useful on Windows&lt;/h1&gt;\\n\\n&lt;h1&gt;arch: i386&lt;/h1&gt;\\n\\n&lt;h1&gt;arch: x86_64&lt;/h1&gt;\\n\\n&lt;h1&gt;Extra directories used by stack for building&lt;/h1&gt;\\n\\n&lt;h1&gt;extra-include-dirs: [/path/to/dir]&lt;/h1&gt;\\n\\n&lt;h1&gt;extra-lib-dirs: [/path/to/dir]&lt;/h1&gt;\\n\\n&lt;h1&gt;Allow a newer minor version of GHC than the snapshot specifies&lt;/h1&gt;\\n\\n&lt;h1&gt;compiler-check: newer-minor&lt;/h1&gt;\\n\\n&lt;p&gt;extra-deps:\\n - minisat-solver-0.1@sha256:e2ff11b1ca8c66e43f8bb2e04f21bd1b812efb94ff215d74f998c928e7e92dcd,5210&lt;/p&gt;\\n\\n&lt;p&gt;```&lt;/p&gt;\\n\\n&lt;p&gt;The cabal file&lt;/p&gt;\\n\\n&lt;p&gt;```\\ncabal-version: 1.12&lt;/p&gt;\\n\\n&lt;h2&gt;-- This file has been generated from package.yaml by hpack version 0.31.2.&lt;/h2&gt;\\n\\n&lt;h2&gt;-- see: &lt;a href=\\\"https://github.com/sol/hpack\\\"&gt;https://github.com/sol/hpack&lt;/a&gt;&lt;/h2&gt;\\n\\n&lt;p&gt;-- hash: 9e4c1b8d2c640f6364c7abf13e184823a0c4b7959a05310c93a9b6ff92efad16&lt;/p&gt;\\n\\n&lt;p&gt;name:           dtl-model-checking\\nversion:        0.1.0.0\\ndescription:    Please see the README on GitHub at &lt;a href=\\\"https://github.com/githubuser/dtl-model-checking#readme\\\"&gt;https://github.com/githubuser/dtl-model-checking#readme&lt;/a&gt;\\nhomepage:       &lt;a href=\\\"https://github.com/githubuser/dtl-model-checking#readme\\\"&gt;https://github.com/githubuser/dtl-model-checking#readme&lt;/a&gt;\\nbug-reports:    &lt;a href=\\\"https://github.com/githubuser/dtl-model-checking/issues\\\"&gt;https://github.com/githubuser/dtl-model-checking/issues&lt;/a&gt;\\nauthor:         Author name here\\nmaintainer:     &lt;a href=\\\"mailto:example@example.com\\\"&gt;example@example.com&lt;/a&gt;\\ncopyright:      2020 Author name here\\nlicense:        BSD3\\nlicense-file:   LICENSE\\nbuild-type:     Simple\\nextra-source-files:\\n    README.md\\n    ChangeLog.md&lt;/p&gt;\\n\\n&lt;p&gt;source-repository head\\n  type: git\\n  location: &lt;a href=\\\"https://github.com/githubuser/dtl-model-checking\\\"&gt;https://github.com/githubuser/dtl-model-checking&lt;/a&gt;&lt;/p&gt;\\n\\n&lt;p&gt;library\\n  exposed-modules:\\n      Automaton\\n      DTLFormula\\n      AutomataTheoreticApproach\\n      DTS\\n      NBA\\n      GNBA\\n      Ielementary\\n      CommonTypes\\n      Utils\\n      ExampleInstances\\n      BMC\\n  other-modules:\\n      Paths_dtl_model_checking\\n  hs-source-dirs:\\n      src\\n  build-depends:\\n      base &amp;gt;=4.7 &amp;amp;&amp;amp; &amp;lt;5\\n    , containers\\n    , random\\n    , minisat-solver &amp;gt;= 0.1\\n  default-language: Haskell2010&lt;/p&gt;\\n\\n&lt;p&gt;executable dtl-model-checking-exe\\n  main-is: Main.hs\\n  other-modules:\\n      Paths_dtl_model_checking\\n  hs-source-dirs:\\n      app\\n  ghc-options: -O -threaded -rtsopts -with-rtsopts=-N\\n  build-depends:\\n      base &amp;gt;=4.7 &amp;amp;&amp;amp; &amp;lt;5\\n    , dtl-model-checking\\n    , containers\\n    , random\\n  default-language: Haskell2010&lt;/p&gt;\\n\\n&lt;p&gt;test-suite dtl-model-checking-test\\n  type: exitcode-stdio-1.0\\n  main-is: Spec.hs\\n  other-modules:\\n      Paths_dtl_model_checking\\n  hs-source-dirs:\\n      test\\n  ghc-options: -O -threaded -rtsopts -with-rtsopts=-N\\n  build-depends:\\n      base &amp;gt;=4.7 &amp;amp;&amp;amp; &amp;lt;5\\n    , dtl-model-checking\\n    , containers\\n    , hspec\\n    , random\\n  default-language: Haskell2010&lt;/p&gt;\\n\\n&lt;p&gt;benchmark dtl-model-checking-benchmark\\n  type: exitcode-stdio-1.0 \\n  main-is: Bench.hs\\n  other-modules:\\n      Paths_dtl_model_checking\\n  hs-source-dirs:\\n      benchmark\\n  ghc-options: -O -threaded -fforce-recomp -rtsopts -with-rtsopts=-N\\n  build-depends: base &amp;gt;=4.7 &amp;amp;&amp;amp; &amp;lt;5, dtl-model-checking, containers, criterion, random\\n  default-language: Haskell2010\\n```&lt;/p&gt;\\n&lt;/div&gt;&lt;!-- SC_ON --&gt;"
                          )
                        , ( "likes" , Null )
                        , ( "suggested_sort" , Null )
                        , ( "banned_at_utc" , Null )
                        , ( "view_count" , Null )
                        , ( "archived" , Boolean False )
                        , ( "no_follow" , Boolean True )
                        , ( "is_crosspostable" , Boolean False )
                        , ( "pinned" , Boolean False )
                        , ( "over_18" , Boolean False )
                        , ( "all_awardings" , Array [] )
                        , ( "awarders" , Array [] )
                        , ( "media_only" , Boolean False )
                        , ( "can_gild" , Boolean False )
                        , ( "spoiler" , Boolean False )
                        , ( "locked" , Boolean False )
                        , ( "author_flair_text" , Null )
                        , ( "treatment_tags" , Array [] )
                        , ( "visited" , Boolean False )
                        , ( "removed_by" , Null )
                        , ( "num_reports" , Null )
                        , ( "distinguished" , Null )
                        , ( "subreddit_id" , String "t5_2qh36" )
                        , ( "mod_reason_by" , Null )
                        , ( "removal_reason" , Null )
                        , ( "link_flair_background_color" , String "" )
                        , ( "id" , String "gmoik7" )
                        , ( "is_robot_indexable" , Boolean True )
                        , ( "report_reasons" , Null )
                        , ( "author" , String "augustoperes" )
                        , ( "discussion_type" , Null )
                        , ( "num_comments" , Number (2 % 1) )
                        , ( "send_replies" , Boolean True )
                        , ( "whitelist_status" , String "all_ads" )
                        , ( "contest_mode" , Boolean False )
                        , ( "mod_reports" , Array [] )
                        , ( "author_patreon_flair" , Boolean False )
                        , ( "author_flair_text_color" , Null )
                        , ( "permalink"
                          , String "/r/haskell/comments/gmoik7/errorwarning_on_stack_build/"
                          )
                        , ( "parent_whitelist_status" , String "all_ads" )
                        , ( "stickied" , Boolean False )
                        , ( "url"
                          , String
                              "https://old.reddit.com/r/haskell/comments/gmoik7/errorwarning_on_stack_build/"
                          )
                        , ( "subreddit_subscribers" , Number (55194 % 1) )
                        , ( "created_utc" , Number (1589894754 % 1) )
                        , ( "num_crossposts" , Number (0 % 1) )
                        , ( "media" , Null )
                        , ( "is_video" , Boolean False )
                        ]
                    )
                  ]
              , Object
                  [ ( "kind" , String "t3" )
                  , ( "data"
                    , Object
                        [ ( "approved_at_utc" , Null )
                        , ( "subreddit" , String "haskell" )
                        , ( "selftext"
                          , String
                              "Do you have any examples of libraries in other languages or language features, which really should have implemented a well-known concept (Monoid, Monad, Alternative, whatever), but they fell short because they (probably) didn't know the concept? For example a broken law, a missing function, over-complicated function types, etc.\\n\\nI encountered multiple such examples, and they always grind my gears. But for the life of me, I can't remember any of them now."
                          )
                        , ( "author_fullname" , String "t2_b7rje" )
                        , ( "saved" , Boolean False )
                        , ( "mod_reason_title" , Null )
                        , ( "gilded" , Number (0 % 1) )
                        , ( "clicked" , Boolean False )
                        , ( "title"
                          , String "Examples of Incorrect Abstractions in Other Languages"
                          )
                        , ( "link_flair_richtext" , Array [] )
                        , ( "subreddit_name_prefixed" , String "r/haskell" )
                        , ( "hidden" , Boolean False )
                        , ( "pwls" , Number (6 % 1) )
                        , ( "link_flair_css_class" , Null )
                        , ( "downs" , Number (0 % 1) )
                        , ( "hide_score" , Boolean False )
                        , ( "name" , String "t3_glz389" )
                        , ( "quarantine" , Boolean False )
                        , ( "link_flair_text_color" , String "dark" )
                        , ( "upvote_ratio" , Number (4368491638549381 % 4503599627370496) )
                        , ( "author_flair_background_color" , Null )
                        , ( "subreddit_type" , String "public" )
                        , ( "ups" , Number (103 % 1) )
                        , ( "total_awards_received" , Number (0 % 1) )
                        , ( "media_embed" , Object [] )
                        , ( "author_flair_template_id" , Null )
                        , ( "is_original_content" , Boolean False )
                        , ( "user_reports" , Array [] )
                        , ( "secure_media" , Null )
                        , ( "is_reddit_media_domain" , Boolean False )
                        , ( "is_meta" , Boolean False )
                        , ( "category" , Null )
                        , ( "secure_media_embed" , Object [] )
                        , ( "link_flair_text" , Null )
                        , ( "can_mod_post" , Boolean False )
                        , ( "score" , Number (103 % 1) )
                        , ( "approved_by" , Null )
                        , ( "author_premium" , Boolean False )
                        , ( "thumbnail" , String "" )
                        , ( "edited" , Boolean False )
                        , ( "author_flair_css_class" , Null )
                        , ( "author_flair_richtext" , Array [] )
                        , ( "gildings" , Object [] )
                        , ( "content_categories" , Null )
                        , ( "is_self" , Boolean True )
                        , ( "mod_note" , Null )
                        , ( "created" , Number (1589827048 % 1) )
                        , ( "link_flair_type" , String "text" )
                        , ( "wls" , Number (6 % 1) )
                        , ( "removed_by_category" , Null )
                        , ( "banned_by" , Null )
                        , ( "author_flair_type" , String "text" )
                        , ( "domain" , String "self.haskell" )
                        , ( "allow_live_comments" , Boolean False )
                        , ( "selftext_html"
                          , String
                              "&lt;!-- SC_OFF --&gt;&lt;div class=\\\"md\\\"&gt;&lt;p&gt;Do you have any examples of libraries in other languages or language features, which really should have implemented a well-known concept (Monoid, Monad, Alternative, whatever), but they fell short because they (probably) didn&amp;#39;t know the concept? For example a broken law, a missing function, over-complicated function types, etc.&lt;/p&gt;\\n\\n&lt;p&gt;I encountered multiple such examples, and they always grind my gears. But for the life of me, I can&amp;#39;t remember any of them now.&lt;/p&gt;\\n&lt;/div&gt;&lt;!-- SC_ON --&gt;"
                          )
                        , ( "likes" , Null )
                        , ( "suggested_sort" , Null )
                        , ( "banned_at_utc" , Null )
                        , ( "view_count" , Null )
                        , ( "archived" , Boolean False )
                        , ( "no_follow" , Boolean False )
                        , ( "is_crosspostable" , Boolean False )
                        , ( "pinned" , Boolean False )
                        , ( "over_18" , Boolean False )
                        , ( "all_awardings" , Array [] )
                        , ( "awarders" , Array [] )
                        , ( "media_only" , Boolean False )
                        , ( "can_gild" , Boolean False )
                        , ( "spoiler" , Boolean False )
                        , ( "locked" , Boolean False )
                        , ( "author_flair_text" , Null )
                        , ( "treatment_tags" , Array [] )
                        , ( "visited" , Boolean False )
                        , ( "removed_by" , Null )
                        , ( "num_reports" , Null )
                        , ( "distinguished" , Null )
                        , ( "subreddit_id" , String "t5_2qh36" )
                        , ( "mod_reason_by" , Null )
                        , ( "removal_reason" , Null )
                        , ( "link_flair_background_color" , String "" )
                        , ( "id" , String "glz389" )
                        , ( "is_robot_indexable" , Boolean True )
                        , ( "report_reasons" , Null )
                        , ( "author" , String "pavelpotocek" )
                        , ( "discussion_type" , Null )
                        , ( "num_comments" , Number (175 % 1) )
                        , ( "send_replies" , Boolean True )
                        , ( "whitelist_status" , String "all_ads" )
                        , ( "contest_mode" , Boolean False )
                        , ( "mod_reports" , Array [] )
                        , ( "author_patreon_flair" , Boolean False )
                        , ( "author_flair_text_color" , Null )
                        , ( "permalink"
                          , String
                              "/r/haskell/comments/glz389/examples_of_incorrect_abstractions_in_other/"
                          )
                        , ( "parent_whitelist_status" , String "all_ads" )
                        , ( "stickied" , Boolean False )
                        , ( "url"
                          , String
                              "https://old.reddit.com/r/haskell/comments/glz389/examples_of_incorrect_abstractions_in_other/"
                          )
                        , ( "subreddit_subscribers" , Number (55194 % 1) )
                        , ( "created_utc" , Number (1589798248 % 1) )
                        , ( "num_crossposts" , Number (0 % 1) )
                        , ( "media" , Null )
                        , ( "is_video" , Boolean False )
                        ]
                    )
                  ]
              , Object
                  [ ( "kind" , String "t3" )
                  , ( "data"
                    , Object
                        [ ( "approved_at_utc" , Null )
                        , ( "subreddit" , String "haskell" )
                        , ( "selftext" , String "" )
                        , ( "author_fullname" , String "t2_2o6ongui" )
                        , ( "saved" , Boolean False )
                        , ( "mod_reason_title" , Null )
                        , ( "gilded" , Number (0 % 1) )
                        , ( "clicked" , Boolean False )
                        , ( "title" , String "[ANN] Medea - a json schema language" )
                        , ( "link_flair_richtext" , Array [] )
                        , ( "subreddit_name_prefixed" , String "r/haskell" )
                        , ( "hidden" , Boolean False )
                        , ( "pwls" , Number (6 % 1) )
                        , ( "link_flair_css_class" , Null )
                        , ( "downs" , Number (0 % 1) )
                        , ( "hide_score" , Boolean False )
                        , ( "name" , String "t3_gma3p4" )
                        , ( "quarantine" , Boolean False )
                        , ( "link_flair_text_color" , String "dark" )
                        , ( "upvote_ratio" , Number (8376695306909123 % 9007199254740992) )
                        , ( "author_flair_background_color" , Null )
                        , ( "subreddit_type" , String "public" )
                        , ( "ups" , Number (11 % 1) )
                        , ( "total_awards_received" , Number (0 % 1) )
                        , ( "media_embed" , Object [] )
                        , ( "author_flair_template_id" , Null )
                        , ( "is_original_content" , Boolean False )
                        , ( "user_reports" , Array [] )
                        , ( "secure_media" , Null )
                        , ( "is_reddit_media_domain" , Boolean False )
                        , ( "is_meta" , Boolean False )
                        , ( "category" , Null )
                        , ( "secure_media_embed" , Object [] )
                        , ( "link_flair_text" , Null )
                        , ( "can_mod_post" , Boolean False )
                        , ( "score" , Number (11 % 1) )
                        , ( "approved_by" , Null )
                        , ( "author_premium" , Boolean False )
                        , ( "thumbnail" , String "" )
                        , ( "edited" , Boolean False )
                        , ( "author_flair_css_class" , Null )
                        , ( "author_flair_richtext" , Array [] )
                        , ( "gildings" , Object [] )
                        , ( "content_categories" , Null )
                        , ( "is_self" , Boolean False )
                        , ( "mod_note" , Null )
                        , ( "created" , Number (1589864384 % 1) )
                        , ( "link_flair_type" , String "text" )
                        , ( "wls" , Number (6 % 1) )
                        , ( "removed_by_category" , Null )
                        , ( "banned_by" , Null )
                        , ( "author_flair_type" , String "text" )
                        , ( "domain" , String "github.com" )
                        , ( "allow_live_comments" , Boolean False )
                        , ( "selftext_html" , Null )
                        , ( "likes" , Null )
                        , ( "suggested_sort" , Null )
                        , ( "banned_at_utc" , Null )
                        , ( "view_count" , Null )
                        , ( "archived" , Boolean False )
                        , ( "no_follow" , Boolean False )
                        , ( "is_crosspostable" , Boolean False )
                        , ( "pinned" , Boolean False )
                        , ( "over_18" , Boolean False )
                        , ( "all_awardings" , Array [] )
                        , ( "awarders" , Array [] )
                        , ( "media_only" , Boolean False )
                        , ( "can_gild" , Boolean False )
                        , ( "spoiler" , Boolean False )
                        , ( "locked" , Boolean False )
                        , ( "author_flair_text" , Null )
                        , ( "treatment_tags" , Array [] )
                        , ( "visited" , Boolean False )
                        , ( "removed_by" , Null )
                        , ( "num_reports" , Null )
                        , ( "distinguished" , Null )
                        , ( "subreddit_id" , String "t5_2qh36" )
                        , ( "mod_reason_by" , Null )
                        , ( "removal_reason" , Null )
                        , ( "link_flair_background_color" , String "" )
                        , ( "id" , String "gma3p4" )
                        , ( "is_robot_indexable" , Boolean True )
                        , ( "report_reasons" , Null )
                        , ( "author" , String "restarted_mustard" )
                        , ( "discussion_type" , Null )
                        , ( "num_comments" , Number (2 % 1) )
                        , ( "send_replies" , Boolean True )
                        , ( "whitelist_status" , String "all_ads" )
                        , ( "contest_mode" , Boolean False )
                        , ( "mod_reports" , Array [] )
                        , ( "author_patreon_flair" , Boolean False )
                        , ( "author_flair_text_color" , Null )
                        , ( "permalink"
                          , String
                              "/r/haskell/comments/gma3p4/ann_medea_a_json_schema_language/"
                          )
                        , ( "parent_whitelist_status" , String "all_ads" )
                        , ( "stickied" , Boolean False )
                        , ( "url" , String "https://github.com/juspay/medea" )
                        , ( "subreddit_subscribers" , Number (55194 % 1) )
                        , ( "created_utc" , Number (1589835584 % 1) )
                        , ( "num_crossposts" , Number (0 % 1) )
                        , ( "media" , Null )
                        , ( "is_video" , Boolean False )
                        ]
                    )
                  ]
              , Object
                  [ ( "kind" , String "t3" )
                  , ( "data"
                    , Object
                        [ ( "approved_at_utc" , Null )
                        , ( "subreddit" , String "haskell" )
                        , ( "selftext"
                          , String
                              "There seem to be some [posts](https://www.reddit.com/r/haskell/comments/pen8s/anyone_else_used_write_yourself_a_scheme_in_48/) about the book or the [Write You a Scheme V2.0](https://wespiser.com/writings/wyas/00_overview.html), but I'm unsure how much Scheme I need to tackle this project.\\n\\nI've thumbed through the (in)famous Learn You a Haskell, and implementing an interpreter sounds like a lot of fun, but perhaps I might not down this path if I have to spend the time to buckle down and learn some Scheme syntax too."
                          )
                        , ( "author_fullname" , String "t2_5y26z8w2" )
                        , ( "saved" , Boolean False )
                        , ( "mod_reason_title" , Null )
                        , ( "gilded" , Number (0 % 1) )
                        , ( "clicked" , Boolean False )
                        , ( "title"
                          , String
                              "How much Scheme needed for \\\"Write yourself a Scheme in 48 hours?\\\""
                          )
                        , ( "link_flair_richtext" , Array [] )
                        , ( "subreddit_name_prefixed" , String "r/haskell" )
                        , ( "hidden" , Boolean False )
                        , ( "pwls" , Number (6 % 1) )
                        , ( "link_flair_css_class" , Null )
                        , ( "downs" , Number (0 % 1) )
                        , ( "hide_score" , Boolean False )
                        , ( "name" , String "t3_gm3ia1" )
                        , ( "quarantine" , Boolean False )
                        , ( "link_flair_text_color" , String "dark" )
                        , ( "upvote_ratio" , Number (4368491638549381 % 4503599627370496) )
                        , ( "author_flair_background_color" , Null )
                        , ( "subreddit_type" , String "public" )
                        , ( "ups" , Number (21 % 1) )
                        , ( "total_awards_received" , Number (0 % 1) )
                        , ( "media_embed" , Object [] )
                        , ( "author_flair_template_id" , Null )
                        , ( "is_original_content" , Boolean False )
                        , ( "user_reports" , Array [] )
                        , ( "secure_media" , Null )
                        , ( "is_reddit_media_domain" , Boolean False )
                        , ( "is_meta" , Boolean False )
                        , ( "category" , Null )
                        , ( "secure_media_embed" , Object [] )
                        , ( "link_flair_text" , Null )
                        , ( "can_mod_post" , Boolean False )
                        , ( "score" , Number (21 % 1) )
                        , ( "approved_by" , Null )
                        , ( "author_premium" , Boolean False )
                        , ( "thumbnail" , String "" )
                        , ( "edited" , Boolean False )
                        , ( "author_flair_css_class" , Null )
                        , ( "author_flair_richtext" , Array [] )
                        , ( "gildings" , Object [] )
                        , ( "content_categories" , Null )
                        , ( "is_self" , Boolean True )
                        , ( "mod_note" , Null )
                        , ( "created" , Number (1589844357 % 1) )
                        , ( "link_flair_type" , String "text" )
                        , ( "wls" , Number (6 % 1) )
                        , ( "removed_by_category" , Null )
                        , ( "banned_by" , Null )
                        , ( "author_flair_type" , String "text" )
                        , ( "domain" , String "self.haskell" )
                        , ( "allow_live_comments" , Boolean False )
                        , ( "selftext_html"
                          , String
                              "&lt;!-- SC_OFF --&gt;&lt;div class=\\\"md\\\"&gt;&lt;p&gt;There seem to be some &lt;a href=\\\"https://www.reddit.com/r/haskell/comments/pen8s/anyone_else_used_write_yourself_a_scheme_in_48/\\\"&gt;posts&lt;/a&gt; about the book or the &lt;a href=\\\"https://wespiser.com/writings/wyas/00_overview.html\\\"&gt;Write You a Scheme V2.0&lt;/a&gt;, but I&amp;#39;m unsure how much Scheme I need to tackle this project.&lt;/p&gt;\\n\\n&lt;p&gt;I&amp;#39;ve thumbed through the (in)famous Learn You a Haskell, and implementing an interpreter sounds like a lot of fun, but perhaps I might not down this path if I have to spend the time to buckle down and learn some Scheme syntax too.&lt;/p&gt;\\n&lt;/div&gt;&lt;!-- SC_ON --&gt;"
                          )
                        , ( "likes" , Null )
                        , ( "suggested_sort" , Null )
                        , ( "banned_at_utc" , Null )
                        , ( "view_count" , Null )
                        , ( "archived" , Boolean False )
                        , ( "no_follow" , Boolean False )
                        , ( "is_crosspostable" , Boolean False )
                        , ( "pinned" , Boolean False )
                        , ( "over_18" , Boolean False )
                        , ( "all_awardings" , Array [] )
                        , ( "awarders" , Array [] )
                        , ( "media_only" , Boolean False )
                        , ( "can_gild" , Boolean False )
                        , ( "spoiler" , Boolean False )
                        , ( "locked" , Boolean False )
                        , ( "author_flair_text" , Null )
                        , ( "treatment_tags" , Array [] )
                        , ( "visited" , Boolean False )
                        , ( "removed_by" , Null )
                        , ( "num_reports" , Null )
                        , ( "distinguished" , Null )
                        , ( "subreddit_id" , String "t5_2qh36" )
                        , ( "mod_reason_by" , Null )
                        , ( "removal_reason" , Null )
                        , ( "link_flair_background_color" , String "" )
                        , ( "id" , String "gm3ia1" )
                        , ( "is_robot_indexable" , Boolean True )
                        , ( "report_reasons" , Null )
                        , ( "author" , String "0x2fwhc" )
                        , ( "discussion_type" , Null )
                        , ( "num_comments" , Number (5 % 1) )
                        , ( "send_replies" , Boolean False )
                        , ( "whitelist_status" , String "all_ads" )
                        , ( "contest_mode" , Boolean False )
                        , ( "mod_reports" , Array [] )
                        , ( "author_patreon_flair" , Boolean False )
                        , ( "author_flair_text_color" , Null )
                        , ( "permalink"
                          , String
                              "/r/haskell/comments/gm3ia1/how_much_scheme_needed_for_write_yourself_a/"
                          )
                        , ( "parent_whitelist_status" , String "all_ads" )
                        , ( "stickied" , Boolean False )
                        , ( "url"
                          , String
                              "https://old.reddit.com/r/haskell/comments/gm3ia1/how_much_scheme_needed_for_write_yourself_a/"
                          )
                        , ( "subreddit_subscribers" , Number (55194 % 1) )
                        , ( "created_utc" , Number (1589815557 % 1) )
                        , ( "num_crossposts" , Number (0 % 1) )
                        , ( "media" , Null )
                        , ( "is_video" , Boolean False )
                        ]
                    )
                  ]
              , Object
                  [ ( "kind" , String "t3" )
                  , ( "data"
                    , Object
                        [ ( "approved_at_utc" , Null )
                        , ( "subreddit" , String "haskell" )
                        , ( "selftext"
                          , String
                              "GHC has releases versions 8.4.x, and 8.6.x, but there are no 8.5.x releases. Why does GHC skip odd minor versions?"
                          )
                        , ( "author_fullname" , String "t2_2lv4dufx" )
                        , ( "saved" , Boolean False )
                        , ( "mod_reason_title" , Null )
                        , ( "gilded" , Number (0 % 1) )
                        , ( "clicked" , Boolean False )
                        , ( "title" , String "GHC versioning scheme" )
                        , ( "link_flair_richtext" , Array [] )
                        , ( "subreddit_name_prefixed" , String "r/haskell" )
                        , ( "hidden" , Boolean False )
                        , ( "pwls" , Number (6 % 1) )
                        , ( "link_flair_css_class" , Null )
                        , ( "downs" , Number (0 % 1) )
                        , ( "hide_score" , Boolean False )
                        , ( "name" , String "t3_gm6mm7" )
                        , ( "quarantine" , Boolean False )
                        , ( "link_flair_text_color" , String "dark" )
                        , ( "upvote_ratio" , Number (1 % 1) )
                        , ( "author_flair_background_color" , Null )
                        , ( "subreddit_type" , String "public" )
                        , ( "ups" , Number (9 % 1) )
                        , ( "total_awards_received" , Number (0 % 1) )
                        , ( "media_embed" , Object [] )
                        , ( "author_flair_template_id" , Null )
                        , ( "is_original_content" , Boolean False )
                        , ( "user_reports" , Array [] )
                        , ( "secure_media" , Null )
                        , ( "is_reddit_media_domain" , Boolean False )
                        , ( "is_meta" , Boolean False )
                        , ( "category" , Null )
                        , ( "secure_media_embed" , Object [] )
                        , ( "link_flair_text" , Null )
                        , ( "can_mod_post" , Boolean False )
                        , ( "score" , Number (9 % 1) )
                        , ( "approved_by" , Null )
                        , ( "author_premium" , Boolean False )
                        , ( "thumbnail" , String "" )
                        , ( "edited" , Boolean False )
                        , ( "author_flair_css_class" , Null )
                        , ( "author_flair_richtext" , Array [] )
                        , ( "gildings" , Object [] )
                        , ( "content_categories" , Null )
                        , ( "is_self" , Boolean True )
                        , ( "mod_note" , Null )
                        , ( "created" , Number (1589853843 % 1) )
                        , ( "link_flair_type" , String "text" )
                        , ( "wls" , Number (6 % 1) )
                        , ( "removed_by_category" , Null )
                        , ( "banned_by" , Null )
                        , ( "author_flair_type" , String "text" )
                        , ( "domain" , String "self.haskell" )
                        , ( "allow_live_comments" , Boolean False )
                        , ( "selftext_html"
                          , String
                              "&lt;!-- SC_OFF --&gt;&lt;div class=\\\"md\\\"&gt;&lt;p&gt;GHC has releases versions 8.4.x, and 8.6.x, but there are no 8.5.x releases. Why does GHC skip odd minor versions?&lt;/p&gt;\\n&lt;/div&gt;&lt;!-- SC_ON --&gt;"
                          )
                        , ( "likes" , Null )
                        , ( "suggested_sort" , Null )
                        , ( "banned_at_utc" , Null )
                        , ( "view_count" , Null )
                        , ( "archived" , Boolean False )
                        , ( "no_follow" , Boolean False )
                        , ( "is_crosspostable" , Boolean False )
                        , ( "pinned" , Boolean False )
                        , ( "over_18" , Boolean False )
                        , ( "all_awardings" , Array [] )
                        , ( "awarders" , Array [] )
                        , ( "media_only" , Boolean False )
                        , ( "can_gild" , Boolean False )
                        , ( "spoiler" , Boolean False )
                        , ( "locked" , Boolean False )
                        , ( "author_flair_text" , Null )
                        , ( "treatment_tags" , Array [] )
                        , ( "visited" , Boolean False )
                        , ( "removed_by" , Null )
                        , ( "num_reports" , Null )
                        , ( "distinguished" , Null )
                        , ( "subreddit_id" , String "t5_2qh36" )
                        , ( "mod_reason_by" , Null )
                        , ( "removal_reason" , Null )
                        , ( "link_flair_background_color" , String "" )
                        , ( "id" , String "gm6mm7" )
                        , ( "is_robot_indexable" , Boolean True )
                        , ( "report_reasons" , Null )
                        , ( "author" , String "NinjaPenguin54" )
                        , ( "discussion_type" , Null )
                        , ( "num_comments" , Number (6 % 1) )
                        , ( "send_replies" , Boolean True )
                        , ( "whitelist_status" , String "all_ads" )
                        , ( "contest_mode" , Boolean False )
                        , ( "mod_reports" , Array [] )
                        , ( "author_patreon_flair" , Boolean False )
                        , ( "author_flair_text_color" , Null )
                        , ( "permalink"
                          , String "/r/haskell/comments/gm6mm7/ghc_versioning_scheme/"
                          )
                        , ( "parent_whitelist_status" , String "all_ads" )
                        , ( "stickied" , Boolean False )
                        , ( "url"
                          , String
                              "https://old.reddit.com/r/haskell/comments/gm6mm7/ghc_versioning_scheme/"
                          )
                        , ( "subreddit_subscribers" , Number (55194 % 1) )
                        , ( "created_utc" , Number (1589825043 % 1) )
                        , ( "num_crossposts" , Number (0 % 1) )
                        , ( "media" , Null )
                        , ( "is_video" , Boolean False )
                        ]
                    )
                  ]
              , Object
                  [ ( "kind" , String "t3" )
                  , ( "data"
                    , Object
                        [ ( "approved_at_utc" , Null )
                        , ( "subreddit" , String "haskell" )
                        , ( "selftext"
                          , String
                              "Hello fellow Haskellers,\\n\\nI've spent last half year learning Haskell and managed to write my first real-world Haskell application. Now I have some ideas for Haskell libraries, that could be (hopefully) useful, but have zero experience designing library for Haskell (mainly from API perspective). Building library is clearly different than building CLI tool, as the main \\\"API\\\" of CLI tool is the command line interface, which is pretty restrictive, but library API should be more flexible to suit different styles and designs of end-user programs. Also if such library is badly designed from start, it's hard to completely change the API style as it breaks compatibility and causes troubles. So I'd like to ask you to share your experience on this topic, mainly following points:\\n\\n1. **handling exceptions** \\\\- I know, this is probably controversial topic, but I'd like to know whether there is any current consensus. Let's say that my library will provide IO operations that may fail because 1/ there is no result for the given input or 2/ there is some IO error (file doesn't exist, etc.). In my CLI tool, I used the approach summarized by u/snoyberg in [this blog post](https://www.fpcomplete.com/blog/2016/11/exceptions-best-practices-haskell), i.e. using `MonadThrow` with `MonadIO`, like `parseJsonFile :: (MonadThrow m, MonadIO m) =&gt; FilePath -&gt; m JSON`. But I'm wondering if this is good approach for library? Because the `MonadThrow` itself isn't really specific about the type of the error it can throw. Would it be better to use something as `MonadError` maybe?\\n2. **RIO** \\\\- In my CLI app I'm pretty happy with [RIO](https://hackage.haskell.org/package/rio), both as Prelude replacement and RIO Monad, but I guess it's not good idea to force end-users to use the RIO-style in library, right?\\n3. **language extensions** \\\\- GHC language extensions are pretty common to use nowadays, but are there any of them I should explicitly avoid using in libraries?\\n4. **overall architecture** \\\\- This is closely related to 1). Should I go full mtl for the library design, or maybe keep it simpler and use just some combination of things like `MonadIO`, `MonadThrow` or `MonadError`?\\n\\nI'll be grateful for any shared experience, comments, links to blog posts/book. Thanks a lot in advance."
                          )
                        , ( "author_fullname" , String "t2_kjucw" )
                        , ( "saved" , Boolean False )
                        , ( "mod_reason_title" , Null )
                        , ( "gilded" , Number (0 % 1) )
                        , ( "clicked" , Boolean False )
                        , ( "title"
                          , String "Designing Haskell library - best practices?"
                          )
                        , ( "link_flair_richtext" , Array [] )
                        , ( "subreddit_name_prefixed" , String "r/haskell" )
                        , ( "hidden" , Boolean False )
                        , ( "pwls" , Number (6 % 1) )
                        , ( "link_flair_css_class" , Null )
                        , ( "downs" , Number (0 % 1) )
                        , ( "hide_score" , Boolean False )
                        , ( "name" , String "t3_gm3v3g" )
                        , ( "quarantine" , Boolean False )
                        , ( "link_flair_text_color" , String "dark" )
                        , ( "upvote_ratio" , Number (7656119366529843 % 9007199254740992) )
                        , ( "author_flair_background_color" , Null )
                        , ( "subreddit_type" , String "public" )
                        , ( "ups" , Number (9 % 1) )
                        , ( "total_awards_received" , Number (0 % 1) )
                        , ( "media_embed" , Object [] )
                        , ( "author_flair_template_id" , Null )
                        , ( "is_original_content" , Boolean False )
                        , ( "user_reports" , Array [] )
                        , ( "secure_media" , Null )
                        , ( "is_reddit_media_domain" , Boolean False )
                        , ( "is_meta" , Boolean False )
                        , ( "category" , Null )
                        , ( "secure_media_embed" , Object [] )
                        , ( "link_flair_text" , Null )
                        , ( "can_mod_post" , Boolean False )
                        , ( "score" , Number (9 % 1) )
                        , ( "approved_by" , Null )
                        , ( "author_premium" , Boolean False )
                        , ( "thumbnail" , String "" )
                        , ( "edited" , Boolean False )
                        , ( "author_flair_css_class" , Null )
                        , ( "author_flair_richtext" , Array [] )
                        , ( "gildings" , Object [] )
                        , ( "content_categories" , Null )
                        , ( "is_self" , Boolean True )
                        , ( "mod_note" , Null )
                        , ( "created" , Number (1589845467 % 1) )
                        , ( "link_flair_type" , String "text" )
                        , ( "wls" , Number (6 % 1) )
                        , ( "removed_by_category" , Null )
                        , ( "banned_by" , Null )
                        , ( "author_flair_type" , String "text" )
                        , ( "domain" , String "self.haskell" )
                        , ( "allow_live_comments" , Boolean False )
                        , ( "selftext_html"
                          , String
                              "&lt;!-- SC_OFF --&gt;&lt;div class=\\\"md\\\"&gt;&lt;p&gt;Hello fellow Haskellers,&lt;/p&gt;\\n\\n&lt;p&gt;I&amp;#39;ve spent last half year learning Haskell and managed to write my first real-world Haskell application. Now I have some ideas for Haskell libraries, that could be (hopefully) useful, but have zero experience designing library for Haskell (mainly from API perspective). Building library is clearly different than building CLI tool, as the main &amp;quot;API&amp;quot; of CLI tool is the command line interface, which is pretty restrictive, but library API should be more flexible to suit different styles and designs of end-user programs. Also if such library is badly designed from start, it&amp;#39;s hard to completely change the API style as it breaks compatibility and causes troubles. So I&amp;#39;d like to ask you to share your experience on this topic, mainly following points:&lt;/p&gt;\\n\\n&lt;ol&gt;\\n&lt;li&gt;&lt;strong&gt;handling exceptions&lt;/strong&gt; - I know, this is probably controversial topic, but I&amp;#39;d like to know whether there is any current consensus. Let&amp;#39;s say that my library will provide IO operations that may fail because 1/ there is no result for the given input or 2/ there is some IO error (file doesn&amp;#39;t exist, etc.). In my CLI tool, I used the approach summarized by &lt;a href=\\\"/u/snoyberg\\\"&gt;u/snoyberg&lt;/a&gt; in &lt;a href=\\\"https://www.fpcomplete.com/blog/2016/11/exceptions-best-practices-haskell\\\"&gt;this blog post&lt;/a&gt;, i.e. using &lt;code&gt;MonadThrow&lt;/code&gt; with &lt;code&gt;MonadIO&lt;/code&gt;, like &lt;code&gt;parseJsonFile :: (MonadThrow m, MonadIO m) =&amp;gt; FilePath -&amp;gt; m JSON&lt;/code&gt;. But I&amp;#39;m wondering if this is good approach for library? Because the &lt;code&gt;MonadThrow&lt;/code&gt; itself isn&amp;#39;t really specific about the type of the error it can throw. Would it be better to use something as &lt;code&gt;MonadError&lt;/code&gt; maybe?&lt;/li&gt;\\n&lt;li&gt;&lt;strong&gt;RIO&lt;/strong&gt; - In my CLI app I&amp;#39;m pretty happy with &lt;a href=\\\"https://hackage.haskell.org/package/rio\\\"&gt;RIO&lt;/a&gt;, both as Prelude replacement and RIO Monad, but I guess it&amp;#39;s not good idea to force end-users to use the RIO-style in library, right?&lt;/li&gt;\\n&lt;li&gt;&lt;strong&gt;language extensions&lt;/strong&gt; - GHC language extensions are pretty common to use nowadays, but are there any of them I should explicitly avoid using in libraries?&lt;/li&gt;\\n&lt;li&gt;&lt;strong&gt;overall architecture&lt;/strong&gt; - This is closely related to 1). Should I go full mtl for the library design, or maybe keep it simpler and use just some combination of things like &lt;code&gt;MonadIO&lt;/code&gt;, &lt;code&gt;MonadThrow&lt;/code&gt; or &lt;code&gt;MonadError&lt;/code&gt;?&lt;/li&gt;\\n&lt;/ol&gt;\\n\\n&lt;p&gt;I&amp;#39;ll be grateful for any shared experience, comments, links to blog posts/book. Thanks a lot in advance.&lt;/p&gt;\\n&lt;/div&gt;&lt;!-- SC_ON --&gt;"
                          )
                        , ( "likes" , Null )
                        , ( "suggested_sort" , Null )
                        , ( "banned_at_utc" , Null )
                        , ( "view_count" , Null )
                        , ( "archived" , Boolean False )
                        , ( "no_follow" , Boolean False )
                        , ( "is_crosspostable" , Boolean False )
                        , ( "pinned" , Boolean False )
                        , ( "over_18" , Boolean False )
                        , ( "all_awardings" , Array [] )
                        , ( "awarders" , Array [] )
                        , ( "media_only" , Boolean False )
                        , ( "can_gild" , Boolean False )
                        , ( "spoiler" , Boolean False )
                        , ( "locked" , Boolean False )
                        , ( "author_flair_text" , Null )
                        , ( "treatment_tags" , Array [] )
                        , ( "visited" , Boolean False )
                        , ( "removed_by" , Null )
                        , ( "num_reports" , Null )
                        , ( "distinguished" , Null )
                        , ( "subreddit_id" , String "t5_2qh36" )
                        , ( "mod_reason_by" , Null )
                        , ( "removal_reason" , Null )
                        , ( "link_flair_background_color" , String "" )
                        , ( "id" , String "gm3v3g" )
                        , ( "is_robot_indexable" , Boolean True )
                        , ( "report_reasons" , Null )
                        , ( "author" , String "xwinus" )
                        , ( "discussion_type" , Null )
                        , ( "num_comments" , Number (5 % 1) )
                        , ( "send_replies" , Boolean True )
                        , ( "whitelist_status" , String "all_ads" )
                        , ( "contest_mode" , Boolean False )
                        , ( "mod_reports" , Array [] )
                        , ( "author_patreon_flair" , Boolean False )
                        , ( "author_flair_text_color" , Null )
                        , ( "permalink"
                          , String
                              "/r/haskell/comments/gm3v3g/designing_haskell_library_best_practices/"
                          )
                        , ( "parent_whitelist_status" , String "all_ads" )
                        , ( "stickied" , Boolean False )
                        , ( "url"
                          , String
                              "https://old.reddit.com/r/haskell/comments/gm3v3g/designing_haskell_library_best_practices/"
                          )
                        , ( "subreddit_subscribers" , Number (55194 % 1) )
                        , ( "created_utc" , Number (1589816667 % 1) )
                        , ( "num_crossposts" , Number (0 % 1) )
                        , ( "media" , Null )
                        , ( "is_video" , Boolean False )
                        ]
                    )
                  ]
              , Object
                  [ ( "kind" , String "t3" )
                  , ( "data"
                    , Object
                        [ ( "approved_at_utc" , Null )
                        , ( "subreddit" , String "haskell" )
                        , ( "selftext"
                          , String
                              "Un dictionnaire en Python peut contenir des donn\195\169es de toute sortes de type.\\n\\nDans ce nouveau chapitre, nous allons utiliser le syst\195\168me de type pour cr\195\169er des enregistrements \194\171 extensibles \194\187, ce qui revient \195\160 appliquer des r\195\168gles de typage aux objets ad hoc des langages dynamiques.\\n\\nC'est un bon pr\195\169texte pour faire un retour sur plusieurs notions d\195\169j\195\160 abord\195\169es : les repr\195\169sentations canoniques, les Types Somme, Produit, existentiels, de rang n et les types de donn\195\169e alg\195\169briques g\195\169n\195\169ralis\195\169s.\\n\\nEn s'exer\195\167ant \195\160 leur usage, nous verrons aussi de nouvelles notions et pratiques, comme :\\n\\n* les types index\195\169s,\\n* les tandems de constructeurs de donn\195\169e dangereux rendus s\195\187r par des constructeurs intelligents,\\n* des \195\169l\195\169ments du module GHC.TypeLits et du paquet first-class-families,\\n* se servir de familles de types comme contrainte ou index sur un type Produit,\\n* les \195\169tiquettes surcharg\195\169es (extension OverloadedLabels) qui permettent de transformer `get (Key @\\\"example\\\") foo` en `get #example foo` (c'est aussi l'occasion de parler d'astuce de contrainte et d'en-t\195\170te d\226\128\153instance).\\n\\nFa\195\174tes circuler l'info s'il vous pla\195\174t, \195\167a me rend bien service.\\n\\nBonne r\195\169flexion !"
                          )
                        , ( "author_fullname" , String "t2_167bmq" )
                        , ( "saved" , Boolean False )
                        , ( "mod_reason_title" , Null )
                        , ( "gilded" , Number (0 % 1) )
                        , ( "clicked" , Boolean False )
                        , ( "title"
                          , String
                              "\\\"Penser en Types\\\" - Chapitre 11 (update in the translation of \\\"Thinking with Types\\\")"
                          )
                        , ( "link_flair_richtext" , Array [] )
                        , ( "subreddit_name_prefixed" , String "r/haskell" )
                        , ( "hidden" , Boolean False )
                        , ( "pwls" , Number (6 % 1) )
                        , ( "link_flair_css_class" , Null )
                        , ( "downs" , Number (0 % 1) )
                        , ( "hide_score" , Boolean False )
                        , ( "name" , String "t3_gm5nzd" )
                        , ( "quarantine" , Boolean False )
                        , ( "link_flair_text_color" , String "dark" )
                        , ( "upvote_ratio" , Number (6034823500676465 % 9007199254740992) )
                        , ( "author_flair_background_color" , Null )
                        , ( "subreddit_type" , String "public" )
                        , ( "ups" , Number (4 % 1) )
                        , ( "total_awards_received" , Number (0 % 1) )
                        , ( "media_embed" , Object [] )
                        , ( "author_flair_template_id" , Null )
                        , ( "is_original_content" , Boolean False )
                        , ( "user_reports" , Array [] )
                        , ( "secure_media" , Null )
                        , ( "is_reddit_media_domain" , Boolean False )
                        , ( "is_meta" , Boolean False )
                        , ( "category" , Null )
                        , ( "secure_media_embed" , Object [] )
                        , ( "link_flair_text" , Null )
                        , ( "can_mod_post" , Boolean False )
                        , ( "score" , Number (4 % 1) )
                        , ( "approved_by" , Null )
                        , ( "author_premium" , Boolean False )
                        , ( "thumbnail" , String "" )
                        , ( "edited" , Boolean False )
                        , ( "author_flair_css_class" , Null )
                        , ( "author_flair_richtext" , Array [] )
                        , ( "gildings" , Object [] )
                        , ( "content_categories" , Null )
                        , ( "is_self" , Boolean True )
                        , ( "mod_note" , Null )
                        , ( "created" , Number (1589850981 % 1) )
                        , ( "link_flair_type" , String "text" )
                        , ( "wls" , Number (6 % 1) )
                        , ( "removed_by_category" , Null )
                        , ( "banned_by" , Null )
                        , ( "author_flair_type" , String "text" )
                        , ( "domain" , String "self.haskell" )
                        , ( "allow_live_comments" , Boolean False )
                        , ( "selftext_html"
                          , String
                              "&lt;!-- SC_OFF --&gt;&lt;div class=\\\"md\\\"&gt;&lt;p&gt;Un dictionnaire en Python peut contenir des donn\195\169es de toute sortes de type.&lt;/p&gt;\\n\\n&lt;p&gt;Dans ce nouveau chapitre, nous allons utiliser le syst\195\168me de type pour cr\195\169er des enregistrements \194\171 extensibles \194\187, ce qui revient \195\160 appliquer des r\195\168gles de typage aux objets ad hoc des langages dynamiques.&lt;/p&gt;\\n\\n&lt;p&gt;C&amp;#39;est un bon pr\195\169texte pour faire un retour sur plusieurs notions d\195\169j\195\160 abord\195\169es : les repr\195\169sentations canoniques, les Types Somme, Produit, existentiels, de rang n et les types de donn\195\169e alg\195\169briques g\195\169n\195\169ralis\195\169s.&lt;/p&gt;\\n\\n&lt;p&gt;En s&amp;#39;exer\195\167ant \195\160 leur usage, nous verrons aussi de nouvelles notions et pratiques, comme :&lt;/p&gt;\\n\\n&lt;ul&gt;\\n&lt;li&gt;les types index\195\169s,&lt;/li&gt;\\n&lt;li&gt;les tandems de constructeurs de donn\195\169e dangereux rendus s\195\187r par des constructeurs intelligents,&lt;/li&gt;\\n&lt;li&gt;des \195\169l\195\169ments du module GHC.TypeLits et du paquet first-class-families,&lt;/li&gt;\\n&lt;li&gt;se servir de familles de types comme contrainte ou index sur un type Produit,&lt;/li&gt;\\n&lt;li&gt;les \195\169tiquettes surcharg\195\169es (extension OverloadedLabels) qui permettent de transformer &lt;code&gt;get (Key @&amp;quot;example&amp;quot;) foo&lt;/code&gt; en &lt;code&gt;get #example foo&lt;/code&gt; (c&amp;#39;est aussi l&amp;#39;occasion de parler d&amp;#39;astuce de contrainte et d&amp;#39;en-t\195\170te d\226\128\153instance).&lt;/li&gt;\\n&lt;/ul&gt;\\n\\n&lt;p&gt;Fa\195\174tes circuler l&amp;#39;info s&amp;#39;il vous pla\195\174t, \195\167a me rend bien service.&lt;/p&gt;\\n\\n&lt;p&gt;Bonne r\195\169flexion !&lt;/p&gt;\\n&lt;/div&gt;&lt;!-- SC_ON --&gt;"
                          )
                        , ( "likes" , Null )
                        , ( "suggested_sort" , Null )
                        , ( "banned_at_utc" , Null )
                        , ( "view_count" , Null )
                        , ( "archived" , Boolean False )
                        , ( "no_follow" , Boolean False )
                        , ( "is_crosspostable" , Boolean False )
                        , ( "pinned" , Boolean False )
                        , ( "over_18" , Boolean False )
                        , ( "all_awardings" , Array [] )
                        , ( "awarders" , Array [] )
                        , ( "media_only" , Boolean False )
                        , ( "can_gild" , Boolean False )
                        , ( "spoiler" , Boolean False )
                        , ( "locked" , Boolean False )
                        , ( "author_flair_text" , Null )
                        , ( "treatment_tags" , Array [] )
                        , ( "visited" , Boolean False )
                        , ( "removed_by" , Null )
                        , ( "num_reports" , Null )
                        , ( "distinguished" , Null )
                        , ( "subreddit_id" , String "t5_2qh36" )
                        , ( "mod_reason_by" , Null )
                        , ( "removal_reason" , Null )
                        , ( "link_flair_background_color" , String "" )
                        , ( "id" , String "gm5nzd" )
                        , ( "is_robot_indexable" , Boolean True )
                        , ( "report_reasons" , Null )
                        , ( "author" , String "jhderaigniac" )
                        , ( "discussion_type" , Null )
                        , ( "num_comments" , Number (0 % 1) )
                        , ( "send_replies" , Boolean True )
                        , ( "whitelist_status" , String "all_ads" )
                        , ( "contest_mode" , Boolean False )
                        , ( "mod_reports" , Array [] )
                        , ( "author_patreon_flair" , Boolean False )
                        , ( "author_flair_text_color" , Null )
                        , ( "permalink"
                          , String
                              "/r/haskell/comments/gm5nzd/penser_en_types_chapitre_11_update_in_the/"
                          )
                        , ( "parent_whitelist_status" , String "all_ads" )
                        , ( "stickied" , Boolean False )
                        , ( "url"
                          , String
                              "https://old.reddit.com/r/haskell/comments/gm5nzd/penser_en_types_chapitre_11_update_in_the/"
                          )
                        , ( "subreddit_subscribers" , Number (55194 % 1) )
                        , ( "created_utc" , Number (1589822181 % 1) )
                        , ( "num_crossposts" , Number (0 % 1) )
                        , ( "media" , Null )
                        , ( "is_video" , Boolean False )
                        ]
                    )
                  ]
              , Object
                  [ ( "kind" , String "t3" )
                  , ( "data"
                    , Object
                        [ ( "approved_at_utc" , Null )
                        , ( "subreddit" , String "haskell" )
                        , ( "selftext"
                          , String
                              "Hello,\\n\\nI could not find the answer anywhere so I thought I might ask here. My package was included in Stackage sometime at the end of April, but it's still not in any LTS release even though there have been a couple of LTS version bumps since then. What is the policy here? Is there anything I should do? Thanks in advance"
                          )
                        , ( "author_fullname" , String "t2_3epm" )
                        , ( "saved" , Boolean False )
                        , ( "mod_reason_title" , Null )
                        , ( "gilded" , Number (0 % 1) )
                        , ( "clicked" , Boolean False )
                        , ( "title"
                          , String "When packages are promoted to LTS in Stackage?"
                          )
                        , ( "link_flair_richtext" , Array [] )
                        , ( "subreddit_name_prefixed" , String "r/haskell" )
                        , ( "hidden" , Boolean False )
                        , ( "pwls" , Number (6 % 1) )
                        , ( "link_flair_css_class" , Null )
                        , ( "downs" , Number (0 % 1) )
                        , ( "hide_score" , Boolean False )
                        , ( "name" , String "t3_gm2484" )
                        , ( "quarantine" , Boolean False )
                        , ( "link_flair_text_color" , String "dark" )
                        , ( "upvote_ratio" , Number (1 % 1) )
                        , ( "author_flair_background_color" , Null )
                        , ( "subreddit_type" , String "public" )
                        , ( "ups" , Number (7 % 1) )
                        , ( "total_awards_received" , Number (0 % 1) )
                        , ( "media_embed" , Object [] )
                        , ( "author_flair_template_id" , Null )
                        , ( "is_original_content" , Boolean False )
                        , ( "user_reports" , Array [] )
                        , ( "secure_media" , Null )
                        , ( "is_reddit_media_domain" , Boolean False )
                        , ( "is_meta" , Boolean False )
                        , ( "category" , Null )
                        , ( "secure_media_embed" , Object [] )
                        , ( "link_flair_text" , Null )
                        , ( "can_mod_post" , Boolean False )
                        , ( "score" , Number (7 % 1) )
                        , ( "approved_by" , Null )
                        , ( "author_premium" , Boolean False )
                        , ( "thumbnail" , String "" )
                        , ( "edited" , Boolean False )
                        , ( "author_flair_css_class" , Null )
                        , ( "author_flair_richtext" , Array [] )
                        , ( "gildings" , Object [] )
                        , ( "content_categories" , Null )
                        , ( "is_self" , Boolean True )
                        , ( "mod_note" , Null )
                        , ( "created" , Number (1589839723 % 1) )
                        , ( "link_flair_type" , String "text" )
                        , ( "wls" , Number (6 % 1) )
                        , ( "removed_by_category" , Null )
                        , ( "banned_by" , Null )
                        , ( "author_flair_type" , String "text" )
                        , ( "domain" , String "self.haskell" )
                        , ( "allow_live_comments" , Boolean False )
                        , ( "selftext_html"
                          , String
                              "&lt;!-- SC_OFF --&gt;&lt;div class=\\\"md\\\"&gt;&lt;p&gt;Hello,&lt;/p&gt;\\n\\n&lt;p&gt;I could not find the answer anywhere so I thought I might ask here. My package was included in Stackage sometime at the end of April, but it&amp;#39;s still not in any LTS release even though there have been a couple of LTS version bumps since then. What is the policy here? Is there anything I should do? Thanks in advance&lt;/p&gt;\\n&lt;/div&gt;&lt;!-- SC_ON --&gt;"
                          )
                        , ( "likes" , Null )
                        , ( "suggested_sort" , Null )
                        , ( "banned_at_utc" , Null )
                        , ( "view_count" , Null )
                        , ( "archived" , Boolean False )
                        , ( "no_follow" , Boolean False )
                        , ( "is_crosspostable" , Boolean False )
                        , ( "pinned" , Boolean False )
                        , ( "over_18" , Boolean False )
                        , ( "all_awardings" , Array [] )
                        , ( "awarders" , Array [] )
                        , ( "media_only" , Boolean False )
                        , ( "can_gild" , Boolean False )
                        , ( "spoiler" , Boolean False )
                        , ( "locked" , Boolean False )
                        , ( "author_flair_text" , Null )
                        , ( "treatment_tags" , Array [] )
                        , ( "visited" , Boolean False )
                        , ( "removed_by" , Null )
                        , ( "num_reports" , Null )
                        , ( "distinguished" , Null )
                        , ( "subreddit_id" , String "t5_2qh36" )
                        , ( "mod_reason_by" , Null )
                        , ( "removal_reason" , Null )
                        , ( "link_flair_background_color" , String "" )
                        , ( "id" , String "gm2484" )
                        , ( "is_robot_indexable" , Boolean True )
                        , ( "report_reasons" , Null )
                        , ( "author" , String "rzeznik" )
                        , ( "discussion_type" , Null )
                        , ( "num_comments" , Number (2 % 1) )
                        , ( "send_replies" , Boolean True )
                        , ( "whitelist_status" , String "all_ads" )
                        , ( "contest_mode" , Boolean False )
                        , ( "mod_reports" , Array [] )
                        , ( "author_patreon_flair" , Boolean False )
                        , ( "author_flair_text_color" , Null )
                        , ( "permalink"
                          , String
                              "/r/haskell/comments/gm2484/when_packages_are_promoted_to_lts_in_stackage/"
                          )
                        , ( "parent_whitelist_status" , String "all_ads" )
                        , ( "stickied" , Boolean False )
                        , ( "url"
                          , String
                              "https://old.reddit.com/r/haskell/comments/gm2484/when_packages_are_promoted_to_lts_in_stackage/"
                          )
                        , ( "subreddit_subscribers" , Number (55194 % 1) )
                        , ( "created_utc" , Number (1589810923 % 1) )
                        , ( "num_crossposts" , Number (0 % 1) )
                        , ( "media" , Null )
                        , ( "is_video" , Boolean False )
                        ]
                    )
                  ]
              , Object
                  [ ( "kind" , String "t3" )
                  , ( "data"
                    , Object
                        [ ( "approved_at_utc" , Null )
                        , ( "subreddit" , String "haskell" )
                        , ( "selftext" , String "" )
                        , ( "author_fullname" , String "t2_o5q8o" )
                        , ( "saved" , Boolean False )
                        , ( "mod_reason_title" , Null )
                        , ( "gilded" , Number (0 % 1) )
                        , ( "clicked" , Boolean False )
                        , ( "title"
                          , String
                              "[ANN] password-2.0: library for working with passwords and password hashes"
                          )
                        , ( "link_flair_richtext" , Array [] )
                        , ( "subreddit_name_prefixed" , String "r/haskell" )
                        , ( "hidden" , Boolean False )
                        , ( "pwls" , Number (6 % 1) )
                        , ( "link_flair_css_class" , Null )
                        , ( "downs" , Number (0 % 1) )
                        , ( "hide_score" , Boolean False )
                        , ( "name" , String "t3_glte2r" )
                        , ( "quarantine" , Boolean False )
                        , ( "link_flair_text_color" , String "dark" )
                        , ( "upvote_ratio" , Number (8376695306909123 % 9007199254740992) )
                        , ( "author_flair_background_color" , Null )
                        , ( "subreddit_type" , String "public" )
                        , ( "ups" , Number (45 % 1) )
                        , ( "total_awards_received" , Number (0 % 1) )
                        , ( "media_embed" , Object [] )
                        , ( "author_flair_template_id" , Null )
                        , ( "is_original_content" , Boolean False )
                        , ( "user_reports" , Array [] )
                        , ( "secure_media" , Null )
                        , ( "is_reddit_media_domain" , Boolean False )
                        , ( "is_meta" , Boolean False )
                        , ( "category" , Null )
                        , ( "secure_media_embed" , Object [] )
                        , ( "link_flair_text" , Null )
                        , ( "can_mod_post" , Boolean False )
                        , ( "score" , Number (45 % 1) )
                        , ( "approved_by" , Null )
                        , ( "author_premium" , Boolean False )
                        , ( "thumbnail" , String "" )
                        , ( "edited" , Boolean False )
                        , ( "author_flair_css_class" , Null )
                        , ( "author_flair_richtext" , Array [] )
                        , ( "gildings" , Object [] )
                        , ( "content_categories" , Null )
                        , ( "is_self" , Boolean False )
                        , ( "mod_note" , Null )
                        , ( "created" , Number (1589800022 % 1) )
                        , ( "link_flair_type" , String "text" )
                        , ( "wls" , Number (6 % 1) )
                        , ( "removed_by_category" , Null )
                        , ( "banned_by" , Null )
                        , ( "author_flair_type" , String "text" )
                        , ( "domain" , String "functor.tokyo" )
                        , ( "allow_live_comments" , Boolean False )
                        , ( "selftext_html" , Null )
                        , ( "likes" , Null )
                        , ( "suggested_sort" , Null )
                        , ( "banned_at_utc" , Null )
                        , ( "view_count" , Null )
                        , ( "archived" , Boolean False )
                        , ( "no_follow" , Boolean False )
                        , ( "is_crosspostable" , Boolean False )
                        , ( "pinned" , Boolean False )
                        , ( "over_18" , Boolean False )
                        , ( "all_awardings" , Array [] )
                        , ( "awarders" , Array [] )
                        , ( "media_only" , Boolean False )
                        , ( "can_gild" , Boolean False )
                        , ( "spoiler" , Boolean False )
                        , ( "locked" , Boolean False )
                        , ( "author_flair_text" , Null )
                        , ( "treatment_tags" , Array [] )
                        , ( "visited" , Boolean False )
                        , ( "removed_by" , Null )
                        , ( "num_reports" , Null )
                        , ( "distinguished" , Null )
                        , ( "subreddit_id" , String "t5_2qh36" )
                        , ( "mod_reason_by" , Null )
                        , ( "removal_reason" , Null )
                        , ( "link_flair_background_color" , String "" )
                        , ( "id" , String "glte2r" )
                        , ( "is_robot_indexable" , Boolean True )
                        , ( "report_reasons" , Null )
                        , ( "author" , String "cdep_illabout" )
                        , ( "discussion_type" , Null )
                        , ( "num_comments" , Number (0 % 1) )
                        , ( "send_replies" , Boolean True )
                        , ( "whitelist_status" , String "all_ads" )
                        , ( "contest_mode" , Boolean False )
                        , ( "mod_reports" , Array [] )
                        , ( "author_patreon_flair" , Boolean False )
                        , ( "author_flair_text_color" , Null )
                        , ( "permalink"
                          , String
                              "/r/haskell/comments/glte2r/ann_password20_library_for_working_with_passwords/"
                          )
                        , ( "parent_whitelist_status" , String "all_ads" )
                        , ( "stickied" , Boolean False )
                        , ( "url"
                          , String "https://functor.tokyo/blog/2020-05-18-password-2.0"
                          )
                        , ( "subreddit_subscribers" , Number (55194 % 1) )
                        , ( "created_utc" , Number (1589771222 % 1) )
                        , ( "num_crossposts" , Number (0 % 1) )
                        , ( "media" , Null )
                        , ( "is_video" , Boolean False )
                        ]
                    )
                  ]
              , Object
                  [ ( "kind" , String "t3" )
                  , ( "data"
                    , Object
                        [ ( "approved_at_utc" , Null )
                        , ( "subreddit" , String "haskell" )
                        , ( "selftext" , String "" )
                        , ( "author_fullname" , String "t2_137hg4" )
                        , ( "saved" , Boolean False )
                        , ( "mod_reason_title" , Null )
                        , ( "gilded" , Number (0 % 1) )
                        , ( "clicked" , Boolean False )
                        , ( "title" , String "Trade-Offs in Type Safety" )
                        , ( "link_flair_richtext" , Array [] )
                        , ( "subreddit_name_prefixed" , String "r/haskell" )
                        , ( "hidden" , Boolean False )
                        , ( "pwls" , Number (6 % 1) )
                        , ( "link_flair_css_class" , Null )
                        , ( "downs" , Number (0 % 1) )
                        , ( "hide_score" , Boolean False )
                        , ( "name" , String "t3_glzz0l" )
                        , ( "quarantine" , Boolean False )
                        , ( "link_flair_text_color" , String "dark" )
                        , ( "upvote_ratio" , Number (1553741871442821 % 2251799813685248) )
                        , ( "author_flair_background_color" , Null )
                        , ( "subreddit_type" , String "public" )
                        , ( "ups" , Number (8 % 1) )
                        , ( "total_awards_received" , Number (0 % 1) )
                        , ( "media_embed" , Object [] )
                        , ( "author_flair_template_id" , Null )
                        , ( "is_original_content" , Boolean False )
                        , ( "user_reports" , Array [] )
                        , ( "secure_media" , Null )
                        , ( "is_reddit_media_domain" , Boolean False )
                        , ( "is_meta" , Boolean False )
                        , ( "category" , Null )
                        , ( "secure_media_embed" , Object [] )
                        , ( "link_flair_text" , Null )
                        , ( "can_mod_post" , Boolean False )
                        , ( "score" , Number (8 % 1) )
                        , ( "approved_by" , Null )
                        , ( "author_premium" , Boolean False )
                        , ( "thumbnail" , String "" )
                        , ( "edited" , Boolean False )
                        , ( "author_flair_css_class" , Null )
                        , ( "author_flair_richtext" , Array [] )
                        , ( "gildings" , Object [] )
                        , ( "content_categories" , Null )
                        , ( "is_self" , Boolean False )
                        , ( "mod_note" , Null )
                        , ( "created" , Number (1589831325 % 1) )
                        , ( "link_flair_type" , String "text" )
                        , ( "wls" , Number (6 % 1) )
                        , ( "removed_by_category" , Null )
                        , ( "banned_by" , Null )
                        , ( "author_flair_type" , String "text" )
                        , ( "domain" , String "alpacaaa.net" )
                        , ( "allow_live_comments" , Boolean False )
                        , ( "selftext_html" , Null )
                        , ( "likes" , Null )
                        , ( "suggested_sort" , Null )
                        , ( "banned_at_utc" , Null )
                        , ( "view_count" , Null )
                        , ( "archived" , Boolean False )
                        , ( "no_follow" , Boolean False )
                        , ( "is_crosspostable" , Boolean False )
                        , ( "pinned" , Boolean False )
                        , ( "over_18" , Boolean False )
                        , ( "all_awardings" , Array [] )
                        , ( "awarders" , Array [] )
                        , ( "media_only" , Boolean False )
                        , ( "can_gild" , Boolean False )
                        , ( "spoiler" , Boolean False )
                        , ( "locked" , Boolean False )
                        , ( "author_flair_text" , Null )
                        , ( "treatment_tags" , Array [] )
                        , ( "visited" , Boolean False )
                        , ( "removed_by" , Null )
                        , ( "num_reports" , Null )
                        , ( "distinguished" , Null )
                        , ( "subreddit_id" , String "t5_2qh36" )
                        , ( "mod_reason_by" , Null )
                        , ( "removal_reason" , Null )
                        , ( "link_flair_background_color" , String "" )
                        , ( "id" , String "glzz0l" )
                        , ( "is_robot_indexable" , Boolean True )
                        , ( "report_reasons" , Null )
                        , ( "author" , String "_alpacaaa" )
                        , ( "discussion_type" , Null )
                        , ( "num_comments" , Number (27 % 1) )
                        , ( "send_replies" , Boolean True )
                        , ( "whitelist_status" , String "all_ads" )
                        , ( "contest_mode" , Boolean False )
                        , ( "mod_reports" , Array [] )
                        , ( "author_patreon_flair" , Boolean False )
                        , ( "author_flair_text_color" , Null )
                        , ( "permalink"
                          , String "/r/haskell/comments/glzz0l/tradeoffs_in_type_safety/"
                          )
                        , ( "parent_whitelist_status" , String "all_ads" )
                        , ( "stickied" , Boolean False )
                        , ( "url" , String "https://alpacaaa.net/type-safety/" )
                        , ( "subreddit_subscribers" , Number (55194 % 1) )
                        , ( "created_utc" , Number (1589802525 % 1) )
                        , ( "num_crossposts" , Number (0 % 1) )
                        , ( "media" , Null )
                        , ( "is_video" , Boolean False )
                        ]
                    )
                  ]
              , Object
                  [ ( "kind" , String "t3" )
                  , ( "data"
                    , Object
                        [ ( "approved_at_utc" , Null )
                        , ( "subreddit" , String "haskell" )
                        , ( "selftext"
                          , String
                              "The Chalmers Online Functional Programming Seminar Series is organized by the Chalmers Functional Programming Group, as a way to exploit the fact that so many of us in the FP community are already meeting and working online these days. Our aim is to bring the people in the FP community closer together, to educate and inspire, and to foster collaboration.\\n\\nThe seminars will take place every Monday (at 7am PDT / 10am EDT / 16:00 CEST) and are **live streamed through YouTube**, and questions are taken through **sli.do**.\\n\\nWe continue tomorrow with Benjamin Pierce; title \\\"Backtracking Generators for Random Testing\\\". All welcome!\\n\\nLink to program, including videos of previous talks:\\n\\nhttp://chalmersfp.org/"
                          )
                        , ( "author_fullname" , String "t2_9ork9" )
                        , ( "saved" , Boolean False )
                        , ( "mod_reason_title" , Null )
                        , ( "gilded" , Number (0 % 1) )
                        , ( "clicked" , Boolean False )
                        , ( "title"
                          , String
                              "Reminder: The Chalmers Online Functional Programming Seminar Series continues tomorrow (Monday) with a talk by Benjamin Pierce"
                          )
                        , ( "link_flair_richtext" , Array [] )
                        , ( "subreddit_name_prefixed" , String "r/haskell" )
                        , ( "hidden" , Boolean False )
                        , ( "pwls" , Number (6 % 1) )
                        , ( "link_flair_css_class" , Null )
                        , ( "downs" , Number (0 % 1) )
                        , ( "hide_score" , Boolean False )
                        , ( "name" , String "t3_gld45o" )
                        , ( "quarantine" , Boolean False )
                        , ( "link_flair_text_color" , String "dark" )
                        , ( "upvote_ratio" , Number (2206763817411543 % 2251799813685248) )
                        , ( "author_flair_background_color" , Null )
                        , ( "subreddit_type" , String "public" )
                        , ( "ups" , Number (89 % 1) )
                        , ( "total_awards_received" , Number (0 % 1) )
                        , ( "media_embed" , Object [] )
                        , ( "author_flair_template_id" , Null )
                        , ( "is_original_content" , Boolean False )
                        , ( "user_reports" , Array [] )
                        , ( "secure_media" , Null )
                        , ( "is_reddit_media_domain" , Boolean False )
                        , ( "is_meta" , Boolean False )
                        , ( "category" , Null )
                        , ( "secure_media_embed" , Object [] )
                        , ( "link_flair_text" , Null )
                        , ( "can_mod_post" , Boolean False )
                        , ( "score" , Number (89 % 1) )
                        , ( "approved_by" , Null )
                        , ( "author_premium" , Boolean False )
                        , ( "thumbnail" , String "" )
                        , ( "edited" , Number (1589711120 % 1) )
                        , ( "author_flair_css_class" , Null )
                        , ( "author_flair_richtext" , Array [] )
                        , ( "gildings" , Object [] )
                        , ( "content_categories" , Null )
                        , ( "is_self" , Boolean True )
                        , ( "mod_note" , Null )
                        , ( "created" , Number (1589739615 % 1) )
                        , ( "link_flair_type" , String "text" )
                        , ( "wls" , Number (6 % 1) )
                        , ( "removed_by_category" , Null )
                        , ( "banned_by" , Null )
                        , ( "author_flair_type" , String "text" )
                        , ( "domain" , String "self.haskell" )
                        , ( "allow_live_comments" , Boolean False )
                        , ( "selftext_html"
                          , String
                              "&lt;!-- SC_OFF --&gt;&lt;div class=\\\"md\\\"&gt;&lt;p&gt;The Chalmers Online Functional Programming Seminar Series is organized by the Chalmers Functional Programming Group, as a way to exploit the fact that so many of us in the FP community are already meeting and working online these days. Our aim is to bring the people in the FP community closer together, to educate and inspire, and to foster collaboration.&lt;/p&gt;\\n\\n&lt;p&gt;The seminars will take place every Monday (at 7am PDT / 10am EDT / 16:00 CEST) and are &lt;strong&gt;live streamed through YouTube&lt;/strong&gt;, and questions are taken through &lt;strong&gt;sli.do&lt;/strong&gt;.&lt;/p&gt;\\n\\n&lt;p&gt;We continue tomorrow with Benjamin Pierce; title &amp;quot;Backtracking Generators for Random Testing&amp;quot;. All welcome!&lt;/p&gt;\\n\\n&lt;p&gt;Link to program, including videos of previous talks:&lt;/p&gt;\\n\\n&lt;p&gt;&lt;a href=\\\"http://chalmersfp.org/\\\"&gt;http://chalmersfp.org/&lt;/a&gt;&lt;/p&gt;\\n&lt;/div&gt;&lt;!-- SC_ON --&gt;"
                          )
                        , ( "likes" , Null )
                        , ( "suggested_sort" , Null )
                        , ( "banned_at_utc" , Null )
                        , ( "view_count" , Null )
                        , ( "archived" , Boolean False )
                        , ( "no_follow" , Boolean False )
                        , ( "is_crosspostable" , Boolean False )
                        , ( "pinned" , Boolean False )
                        , ( "over_18" , Boolean False )
                        , ( "all_awardings" , Array [] )
                        , ( "awarders" , Array [] )
                        , ( "media_only" , Boolean False )
                        , ( "can_gild" , Boolean False )
                        , ( "spoiler" , Boolean False )
                        , ( "locked" , Boolean False )
                        , ( "author_flair_text" , Null )
                        , ( "treatment_tags" , Array [] )
                        , ( "visited" , Boolean False )
                        , ( "removed_by" , Null )
                        , ( "num_reports" , Null )
                        , ( "distinguished" , Null )
                        , ( "subreddit_id" , String "t5_2qh36" )
                        , ( "mod_reason_by" , Null )
                        , ( "removal_reason" , Null )
                        , ( "link_flair_background_color" , String "" )
                        , ( "id" , String "gld45o" )
                        , ( "is_robot_indexable" , Boolean True )
                        , ( "report_reasons" , Null )
                        , ( "author" , String "koenclaessen" )
                        , ( "discussion_type" , Null )
                        , ( "num_comments" , Number (4 % 1) )
                        , ( "send_replies" , Boolean True )
                        , ( "whitelist_status" , String "all_ads" )
                        , ( "contest_mode" , Boolean False )
                        , ( "mod_reports" , Array [] )
                        , ( "author_patreon_flair" , Boolean False )
                        , ( "author_flair_text_color" , Null )
                        , ( "permalink"
                          , String
                              "/r/haskell/comments/gld45o/reminder_the_chalmers_online_functional/"
                          )
                        , ( "parent_whitelist_status" , String "all_ads" )
                        , ( "stickied" , Boolean False )
                        , ( "url"
                          , String
                              "https://old.reddit.com/r/haskell/comments/gld45o/reminder_the_chalmers_online_functional/"
                          )
                        , ( "subreddit_subscribers" , Number (55194 % 1) )
                        , ( "created_utc" , Number (1589710815 % 1) )
                        , ( "num_crossposts" , Number (0 % 1) )
                        , ( "media" , Null )
                        , ( "is_video" , Boolean False )
                        ]
                    )
                  ]
              ]
          )
        , ( "after" , String "t3_gld45o" )
        , ( "before" , Null )
        ]
    )
  ]
[T480:~/code/haskell/json]$ 

dat/old.reddit.com-r-haskell-raw.json

{"kind": "Listing", "data": {"modhash": "", "dist": 26, "children": [{"kind": "t3", "data": {"approved_at_utc": null, "subreddit": "haskell", "selftext": "This is your opportunity to ask any questions you feel don't deserve their own threads, no matter how small or simple they might be!", "author_fullname": "t2_6l4z3", "saved": false, "mod_reason_title": null, "gilded": 0, "clicked": false, "title": "Monthly Hask Anything (May 2020)", "link_flair_richtext": [], "subreddit_name_prefixed": "r/haskell", "hidden": false, "pwls": 6, "link_flair_css_class": null, "downs": 0, "hide_score": false, "name": "t3_gazovx", "quarantine": false, "link_flair_text_color": "dark", "upvote_ratio": 1.0, "author_flair_background_color": null, "subreddit_type": "public", "ups": 20, "total_awards_received": 0, "media_embed": {}, "author_flair_template_id": null, "is_original_content": false, "user_reports": [], "secure_media": null, "is_reddit_media_domain": false, "is_meta": false, "category": null, "secure_media_embed": {}, "link_flair_text": null, "can_mod_post": false, "score": 20, "approved_by": null, "author_premium": true, "thumbnail": "", "edited": false, "author_flair_css_class": null, "author_flair_richtext": [], "gildings": {}, "content_categories": null, "is_self": true, "mod_note": null, "created": 1588295176.0, "link_flair_type": "text", "wls": 6, "removed_by_category": null, "banned_by": null, "author_flair_type": "text", "domain": "self.haskell", "allow_live_comments": false, "selftext_html": "&lt;!-- SC_OFF --&gt;&lt;div class=\"md\"&gt;&lt;p&gt;This is your opportunity to ask any questions you feel don&amp;#39;t deserve their own threads, no matter how small or simple they might be!&lt;/p&gt;\n&lt;/div&gt;&lt;!-- SC_ON --&gt;", "likes": null, "suggested_sort": "new", "banned_at_utc": null, "view_count": null, "archived": false, "no_follow": true, "is_crosspostable": false, "pinned": false, "over_18": false, "all_awardings": [], "awarders": [], "media_only": false, "can_gild": false, "spoiler": false, "locked": false, "author_flair_text": null, "treatment_tags": [], "visited": false, "removed_by": null, "num_reports": null, "distinguished": "moderator", "subreddit_id": "t5_2qh36", "mod_reason_by": null, "removal_reason": null, "link_flair_background_color": "", "id": "gazovx", "is_robot_indexable": true, "report_reasons": null, "author": "AutoModerator", "discussion_type": null, "num_comments": 228, "send_replies": false, "whitelist_status": "all_ads", "contest_mode": false, "mod_reports": [], "author_patreon_flair": false, "author_flair_text_color": null, "permalink": "/r/haskell/comments/gazovx/monthly_hask_anything_may_2020/", "parent_whitelist_status": "all_ads", "stickied": true, "url": "https://old.reddit.com/r/haskell/comments/gazovx/monthly_hask_anything_may_2020/", "subreddit_subscribers": 55194, "created_utc": 1588266376.0, "num_crossposts": 0, "media": null, "is_video": false}}, {"kind": "t3", "data": {"approved_at_utc": null, "subreddit": "haskell", "selftext": "", "author_fullname": "t2_4iein", "saved": false, "mod_reason_title": null, "gilded": 0, "clicked": false, "title": "Haskell Error Message, and How to Improve Them", "link_flair_richtext": [], "subreddit_name_prefixed": "r/haskell", "hidden": false, "pwls": 6, "link_flair_css_class": null, "downs": 0, "hide_score": false, "name": "t3_gnblom", "quarantine": false, "link_flair_text_color": "dark", "upvote_ratio": 0.9, "author_flair_background_color": null, "subreddit_type": "public", "ups": 35, "total_awards_received": 0, "media_embed": {}, "author_flair_template_id": null, "is_original_content": false, "user_reports": [], "secure_media": null, "is_reddit_media_domain": false, "is_meta": false, "category": null, "secure_media_embed": {}, "link_flair_text": null, "can_mod_post": false, "score": 35, "approved_by": null, "author_premium": false, "thumbnail": "", "edited": false, "author_flair_css_class": null, "author_flair_richtext": [], "gildings": {}, "content_categories": null, "is_self": false, "mod_note": null, "created": 1590011148.0, "link_flair_type": "text", "wls": 6, "removed_by_category": null, "banned_by": null, "author_flair_type": "text", "domain": "anthony.noided.media", "allow_live_comments": false, "selftext_html": null, "likes": null, "suggested_sort": null, "banned_at_utc": null, "view_count": null, "archived": false, "no_follow": false, "is_crosspostable": false, "pinned": false, "over_18": false, "all_awardings": [], "awarders": [], "media_only": false, "can_gild": false, "spoiler": false, "locked": false, "author_flair_text": null, "treatment_tags": [], "visited": false, "removed_by": null, "num_reports": null, "distinguished": null, "subreddit_id": "t5_2qh36", "mod_reason_by": null, "removal_reason": null, "link_flair_background_color": "", "id": "gnblom", "is_robot_indexable": true, "report_reasons": null, "author": "THeShinyHObbiest", "discussion_type": null, "num_comments": 32, "send_replies": true, "whitelist_status": "all_ads", "contest_mode": false, "mod_reports": [], "author_patreon_flair": false, "author_flair_text_color": null, "permalink": "/r/haskell/comments/gnblom/haskell_error_message_and_how_to_improve_them/", "parent_whitelist_status": "all_ads", "stickied": false, "url": "https://anthony.noided.media/blog/haskell/programming/2020/05/14/haskell-errors.html", "subreddit_subscribers": 55194, "created_utc": 1589982348.0, "num_crossposts": 0, "media": null, "is_video": false}}, {"kind": "t3", "data": {"approved_at_utc": null, "subreddit": "haskell", "selftext": "Hello dear redditors,\n\nI'm happy to announce my book \"Functional Design and Architecture\".\n\nIt's 80% done (8 chapters of 10, 600k symbols), and I decided to start selling it via Leanpub because it's already the most comprehensive guide on building of real software in Haskell and in FP.\n\n[Functional Design and Architecture (book) on Leanpub](https://leanpub.com/functional-design-and-architecture)\n\nThe book is focussing on many different design patterns, design principles and approaches, but the central role in it plays the approach I call Hierarchical Free Monads. Although the draft of chapters is available online [here](https://graninas.com/functional-design-and-architecture-book/), I won't be uncovering the rest, at least for now. I spent more than 2 years of writing the book, developing the approaches, providing materials and creating showcase projects. And now I think it's not an exaggeration to say that my Hierarchical Free Monads is the most developed approach in Haskell today.\n\nThe book is based on 2 projects, so you can play with the concepts easily:\n\n* [Hydra](https://github.com/graninas/Hydra), a full-fledged framework for building web services, multithreaded and concurrent applications with SQL and KV DB support. Contains 3 engines: Final Tagless, Free Monad and Church Encoded Free Monad, as well as several demo applications to compare these 3 approaches.\n* [Andromeda](https://github.com/graninas/Andromeda), a SCADA software for spaceship control.\n\nI also have a Patreon program for the book:\n\n[Patreon: \"Functional Design and Architecture\"](https://www.patreon.com/functional_design_and_architecture)\n\nAll the money collected from this program will be used to hire professional editors, designers, reviewers. I'm very grateful to all my Patron supporters! The supporters have an access to some exclusive content. They will get a edited book as well.\n\nThe following project is of my design also.\n\n* [Node](https://github.com/graninas/Node), a real-world all-in-one framework which is tested in production. It allows to build network actors and blockchain protocols, console applications, work with KV database and cryptography. Sample but not simple blockchain applications are also provided there.\n\nYou can get familiar with my long read articles explaining the concepts in details:\n\n* [Hierarchical Free Monads: The Most Developed Approach In Haskell (article)](https://github.com/graninas/hierarchical-free-monads-the-most-developed-approach-in-haskell)\n* [Automatic White-Box Testing with Free Monads (article, showcase)](https://github.com/graninas/automatic-whitebox-testing-showcase)\n* [Building network actors with Node Framework](https://gist.github.com/graninas/9beb8df5d88dda5fa21c47ce9bcb0e16)\n\nYou might also want to get familiar with my [list of materials on Software Design in Haskell](https://github.com/graninas/software-design-in-haskell).\n\nI'm also giving talks on this topic. Consider the following talks:\n\n* [Hierarchical Free Monads and Software Design in Functional Programming (talk)](https://www.youtube.com/watch?v=3GKQ4ni2pS0)\n* [Automatic Whitebox Testing with Free Monads (talk)](https://www.youtube.com/watch?v=ciZL-adDpVQ)\n* [Final Tagless vs Free Monads (talk, Russian)](https://www.youtube.com/watch?v=u1GGqDQyGfc) | [slides (English)](https://drive.google.com/open?id=1VhS8ySgk2w5RoN_l_Ar_axcE4Dzf97zLw1uuzUJQbCo)\n\nAnd this list of my materials is not even complete. For the record, I used Free Monads for making my own STM library: in Haskell and in C++. The implementation was incredibly simple due to the power of Free Monads to abstract things. There are different projects:\n\n* [stm-free](https://github.com/graninas/stm-free), my Free Monad based STM library in Haskell;\n* [cpp\\_stm-free](https://github.com/graninas/cpp_stm_free), the port to C++. Even more, it has 2 independent engines: Free Monad based and Church Encoded Free Monad based.\n* [Software Transactional Memory in C++: pure functional approach (Tutorial)](https://gist.github.com/graninas/c7e0a603f3a22c7e85daa4599bf92525) \\- the article, in case you like strange functional programming in C++.\n* [Functional Approach To Software Transactional Memory in C++ (talk, Russian)](https://www.youtube.com/watch?v=VHZPcz8HwZs) | [slides](https://docs.google.com/presentation/d/1_znOLZDKruKRNLA58TDlnXYQjTg9sXNJHPOLHfDTjeU/edit?usp=sharing) (English)\n* [cpp\\_parsec\\_free](https://github.com/graninas/cpp_parsec_free): a PoC of monadic parsers in C++ based on the same idea of Free Monads.\n* [Monadic Parsers in C++ (talk, Russian)](https://www.youtube.com/watch?v=q39PHTJDaLE) | [slides](https://docs.google.com/presentation/d/1zlwKBX8-DYVWUYmzvmKm7ggDVBugEJzY6OFSWjeQOA4/edit?usp=sharing) (English)\n* [hinteractive](https://github.com/graninas/hinteractive), an eDSL-like engine for interactive fiction games like Zork. Free Monad based.\n\nYes, all these projects show that I investigated Free Monads from all possible sides. But even more, there are two open source frameworks I (with my coworkers) designed for our employer, and these projects are heavily used in production:\n\n* [PureScript Presto](https://github.com/juspay/purescript-presto) \\- a framework for building mobile apps using a handy eDSL.\n* [PureScript Presto.Backend](https://github.com/juspay/purescript-presto-backend) \\- a framework for web RESTful backends.\n\nStill not convinced? Follow me ([Twitter](https://twitter.com/graninas), [GitHub](https://github.com/graninas), [LinkedIn](https://www.linkedin.com/in/alexander-granin-46889236/), [Telegram](https://web.telegram.org/#/im?p=@graninas), [Facebook](https://www.facebook.com/alexandr.granin)), hire me, and keep your eyes on my activity. Even more materials are coming!\n\nYours truly,\n\nAlexander Granin", "author_fullname": "t2_geqys", "saved": false, "mod_reason_title": null, "gilded": 0, "clicked": false, "title": "Book \"Functional Design and Architecture\"", "link_flair_richtext": [], "subreddit_name_prefixed": "r/haskell", "hidden": false, "pwls": 6, "link_flair_css_class": null, "downs": 0, "hide_score": false, "name": "t3_gmxfqz", "quarantine": false, "link_flair_text_color": "dark", "upvote_ratio": 0.97, "author_flair_background_color": null, "subreddit_type": "public", "ups": 155, "total_awards_received": 1, "media_embed": {}, "author_flair_template_id": null, "is_original_content": false, "user_reports": [], "secure_media": null, "is_reddit_media_domain": false, "is_meta": false, "category": null, "secure_media_embed": {}, "link_flair_text": null, "can_mod_post": false, "score": 155, "approved_by": null, "author_premium": false, "thumbnail": "", "edited": 1589979013.0, "author_flair_css_class": null, "author_flair_richtext": [], "gildings": {}, "content_categories": null, "is_self": true, "mod_note": null, "created": 1589951620.0, "link_flair_type": "text", "wls": 6, "removed_by_category": null, "banned_by": null, "author_flair_type": "text", "domain": "self.haskell", "allow_live_comments": false, "selftext_html": "&lt;!-- SC_OFF --&gt;&lt;div class=\"md\"&gt;&lt;p&gt;Hello dear redditors,&lt;/p&gt;\n\n&lt;p&gt;I&amp;#39;m happy to announce my book &amp;quot;Functional Design and Architecture&amp;quot;.&lt;/p&gt;\n\n&lt;p&gt;It&amp;#39;s 80% done (8 chapters of 10, 600k symbols), and I decided to start selling it via Leanpub because it&amp;#39;s already the most comprehensive guide on building of real software in Haskell and in FP.&lt;/p&gt;\n\n&lt;p&gt;&lt;a href=\"https://leanpub.com/functional-design-and-architecture\"&gt;Functional Design and Architecture (book) on Leanpub&lt;/a&gt;&lt;/p&gt;\n\n&lt;p&gt;The book is focussing on many different design patterns, design principles and approaches, but the central role in it plays the approach I call Hierarchical Free Monads. Although the draft of chapters is available online &lt;a href=\"https://graninas.com/functional-design-and-architecture-book/\"&gt;here&lt;/a&gt;, I won&amp;#39;t be uncovering the rest, at least for now. I spent more than 2 years of writing the book, developing the approaches, providing materials and creating showcase projects. And now I think it&amp;#39;s not an exaggeration to say that my Hierarchical Free Monads is the most developed approach in Haskell today.&lt;/p&gt;\n\n&lt;p&gt;The book is based on 2 projects, so you can play with the concepts easily:&lt;/p&gt;\n\n&lt;ul&gt;\n&lt;li&gt;&lt;a href=\"https://github.com/graninas/Hydra\"&gt;Hydra&lt;/a&gt;, a full-fledged framework for building web services, multithreaded and concurrent applications with SQL and KV DB support. Contains 3 engines: Final Tagless, Free Monad and Church Encoded Free Monad, as well as several demo applications to compare these 3 approaches.&lt;/li&gt;\n&lt;li&gt;&lt;a href=\"https://github.com/graninas/Andromeda\"&gt;Andromeda&lt;/a&gt;, a SCADA software for spaceship control.&lt;/li&gt;\n&lt;/ul&gt;\n\n&lt;p&gt;I also have a Patreon program for the book:&lt;/p&gt;\n\n&lt;p&gt;&lt;a href=\"https://www.patreon.com/functional_design_and_architecture\"&gt;Patreon: &amp;quot;Functional Design and Architecture&amp;quot;&lt;/a&gt;&lt;/p&gt;\n\n&lt;p&gt;All the money collected from this program will be used to hire professional editors, designers, reviewers. I&amp;#39;m very grateful to all my Patron supporters! The supporters have an access to some exclusive content. They will get a edited book as well.&lt;/p&gt;\n\n&lt;p&gt;The following project is of my design also.&lt;/p&gt;\n\n&lt;ul&gt;\n&lt;li&gt;&lt;a href=\"https://github.com/graninas/Node\"&gt;Node&lt;/a&gt;, a real-world all-in-one framework which is tested in production. It allows to build network actors and blockchain protocols, console applications, work with KV database and cryptography. Sample but not simple blockchain applications are also provided there.&lt;/li&gt;\n&lt;/ul&gt;\n\n&lt;p&gt;You can get familiar with my long read articles explaining the concepts in details:&lt;/p&gt;\n\n&lt;ul&gt;\n&lt;li&gt;&lt;a href=\"https://github.com/graninas/hierarchical-free-monads-the-most-developed-approach-in-haskell\"&gt;Hierarchical Free Monads: The Most Developed Approach In Haskell (article)&lt;/a&gt;&lt;/li&gt;\n&lt;li&gt;&lt;a href=\"https://github.com/graninas/automatic-whitebox-testing-showcase\"&gt;Automatic White-Box Testing with Free Monads (article, showcase)&lt;/a&gt;&lt;/li&gt;\n&lt;li&gt;&lt;a href=\"https://gist.github.com/graninas/9beb8df5d88dda5fa21c47ce9bcb0e16\"&gt;Building network actors with Node Framework&lt;/a&gt;&lt;/li&gt;\n&lt;/ul&gt;\n\n&lt;p&gt;You might also want to get familiar with my &lt;a href=\"https://github.com/graninas/software-design-in-haskell\"&gt;list of materials on Software Design in Haskell&lt;/a&gt;.&lt;/p&gt;\n\n&lt;p&gt;I&amp;#39;m also giving talks on this topic. Consider the following talks:&lt;/p&gt;\n\n&lt;ul&gt;\n&lt;li&gt;&lt;a href=\"https://www.youtube.com/watch?v=3GKQ4ni2pS0\"&gt;Hierarchical Free Monads and Software Design in Functional Programming (talk)&lt;/a&gt;&lt;/li&gt;\n&lt;li&gt;&lt;a href=\"https://www.youtube.com/watch?v=ciZL-adDpVQ\"&gt;Automatic Whitebox Testing with Free Monads (talk)&lt;/a&gt;&lt;/li&gt;\n&lt;li&gt;&lt;a href=\"https://www.youtube.com/watch?v=u1GGqDQyGfc\"&gt;Final Tagless vs Free Monads (talk, Russian)&lt;/a&gt; | &lt;a href=\"https://drive.google.com/open?id=1VhS8ySgk2w5RoN_l_Ar_axcE4Dzf97zLw1uuzUJQbCo\"&gt;slides (English)&lt;/a&gt;&lt;/li&gt;\n&lt;/ul&gt;\n\n&lt;p&gt;And this list of my materials is not even complete. For the record, I used Free Monads for making my own STM library: in Haskell and in C++. The implementation was incredibly simple due to the power of Free Monads to abstract things. There are different projects:&lt;/p&gt;\n\n&lt;ul&gt;\n&lt;li&gt;&lt;a href=\"https://github.com/graninas/stm-free\"&gt;stm-free&lt;/a&gt;, my Free Monad based STM library in Haskell;&lt;/li&gt;\n&lt;li&gt;&lt;a href=\"https://github.com/graninas/cpp_stm_free\"&gt;cpp_stm-free&lt;/a&gt;, the port to C++. Even more, it has 2 independent engines: Free Monad based and Church Encoded Free Monad based.&lt;/li&gt;\n&lt;li&gt;&lt;a href=\"https://gist.github.com/graninas/c7e0a603f3a22c7e85daa4599bf92525\"&gt;Software Transactional Memory in C++: pure functional approach (Tutorial)&lt;/a&gt; - the article, in case you like strange functional programming in C++.&lt;/li&gt;\n&lt;li&gt;&lt;a href=\"https://www.youtube.com/watch?v=VHZPcz8HwZs\"&gt;Functional Approach To Software Transactional Memory in C++ (talk, Russian)&lt;/a&gt; | &lt;a href=\"https://docs.google.com/presentation/d/1_znOLZDKruKRNLA58TDlnXYQjTg9sXNJHPOLHfDTjeU/edit?usp=sharing\"&gt;slides&lt;/a&gt; (English)&lt;/li&gt;\n&lt;li&gt;&lt;a href=\"https://github.com/graninas/cpp_parsec_free\"&gt;cpp_parsec_free&lt;/a&gt;: a PoC of monadic parsers in C++ based on the same idea of Free Monads.&lt;/li&gt;\n&lt;li&gt;&lt;a href=\"https://www.youtube.com/watch?v=q39PHTJDaLE\"&gt;Monadic Parsers in C++ (talk, Russian)&lt;/a&gt; | &lt;a href=\"https://docs.google.com/presentation/d/1zlwKBX8-DYVWUYmzvmKm7ggDVBugEJzY6OFSWjeQOA4/edit?usp=sharing\"&gt;slides&lt;/a&gt; (English)&lt;/li&gt;\n&lt;li&gt;&lt;a href=\"https://github.com/graninas/hinteractive\"&gt;hinteractive&lt;/a&gt;, an eDSL-like engine for interactive fiction games like Zork. Free Monad based.&lt;/li&gt;\n&lt;/ul&gt;\n\n&lt;p&gt;Yes, all these projects show that I investigated Free Monads from all possible sides. But even more, there are two open source frameworks I (with my coworkers) designed for our employer, and these projects are heavily used in production:&lt;/p&gt;\n\n&lt;ul&gt;\n&lt;li&gt;&lt;a href=\"https://github.com/juspay/purescript-presto\"&gt;PureScript Presto&lt;/a&gt; - a framework for building mobile apps using a handy eDSL.&lt;/li&gt;\n&lt;li&gt;&lt;a href=\"https://github.com/juspay/purescript-presto-backend\"&gt;PureScript Presto.Backend&lt;/a&gt; - a framework for web RESTful backends.&lt;/li&gt;\n&lt;/ul&gt;\n\n&lt;p&gt;Still not convinced? Follow me (&lt;a href=\"https://twitter.com/graninas\"&gt;Twitter&lt;/a&gt;, &lt;a href=\"https://github.com/graninas\"&gt;GitHub&lt;/a&gt;, &lt;a href=\"https://www.linkedin.com/in/alexander-granin-46889236/\"&gt;LinkedIn&lt;/a&gt;, &lt;a href=\"https://web.telegram.org/#/im?p=@graninas\"&gt;Telegram&lt;/a&gt;, &lt;a href=\"https://www.facebook.com/alexandr.granin\"&gt;Facebook&lt;/a&gt;), hire me, and keep your eyes on my activity. Even more materials are coming!&lt;/p&gt;\n\n&lt;p&gt;Yours truly,&lt;/p&gt;\n\n&lt;p&gt;Alexander Granin&lt;/p&gt;\n&lt;/div&gt;&lt;!-- SC_ON --&gt;", "likes": null, "suggested_sort": null, "banned_at_utc": null, "view_count": null, "archived": false, "no_follow": false, "is_crosspostable": false, "pinned": false, "over_18": false, "all_awardings": [{"giver_coin_reward": null, "subreddit_id": null, "is_new": false, "days_of_drip_extension": 0, "coin_price": 500, "id": "award_43c43a35-15c5-4f73-91ef-fe538426435a", "penny_donate": null, "coin_reward": 100, "icon_url": "https://i.redd.it/award_images/t5_22cerq/xe5mw55w5v541_BlessUp.png", "days_of_premium": 0, "icon_height": 2048, "resized_icons": [{"url": "https://preview.redd.it/award_images/t5_22cerq/xe5mw55w5v541_BlessUp.png?width=16&amp;height=16&amp;auto=webp&amp;s=e84e08de4b1352e679d612c063584341f56bc2b5", "width": 16, "height": 16}, {"url": "https://preview.redd.it/award_images/t5_22cerq/xe5mw55w5v541_BlessUp.png?width=32&amp;height=32&amp;auto=webp&amp;s=d01d7a3286bb55c235e217736c78c66e2d7d0c18", "width": 32, "height": 32}, {"url": "https://preview.redd.it/award_images/t5_22cerq/xe5mw55w5v541_BlessUp.png?width=48&amp;height=48&amp;auto=webp&amp;s=6ae7d390be614e44f1ec06141d0ba51d65494bff", "width": 48, "height": 48}, {"url": "https://preview.redd.it/award_images/t5_22cerq/xe5mw55w5v541_BlessUp.png?width=64&amp;height=64&amp;auto=webp&amp;s=1c88befd3d95c2ea37b95a7132db98d8a8730ae1", "width": 64, "height": 64}, {"url": "https://preview.redd.it/award_images/t5_22cerq/xe5mw55w5v541_BlessUp.png?width=128&amp;height=128&amp;auto=webp&amp;s=f97d6987f6545f6cb659f1fce7c304278a92f762", "width": 128, "height": 128}], "icon_width": 2048, "start_date": null, "is_enabled": true, "description": "Prayers up for the blessed. Gives %{coin_symbol}100 Coins to both the author and the community.", "end_date": null, "subreddit_coin_reward": 100, "count": 1, "name": "Bless Up (Pro)", "icon_format": null, "award_sub_type": "GLOBAL", "penny_price": null, "award_type": "global"}], "awarders": [], "media_only": false, "can_gild": false, "spoiler": false, "locked": false, "author_flair_text": null, "treatment_tags": [], "visited": false, "removed_by": null, "num_reports": null, "distinguished": null, "subreddit_id": "t5_2qh36", "mod_reason_by": null, "removal_reason": null, "link_flair_background_color": "", "id": "gmxfqz", "is_robot_indexable": true, "report_reasons": null, "author": "graninas", "discussion_type": null, "num_comments": 26, "send_replies": true, "whitelist_status": "all_ads", "contest_mode": false, "mod_reports": [], "author_patreon_flair": false, "author_flair_text_color": null, "permalink": "/r/haskell/comments/gmxfqz/book_functional_design_and_architecture/", "parent_whitelist_status": "all_ads", "stickied": false, "url": "https://old.reddit.com/r/haskell/comments/gmxfqz/book_functional_design_and_architecture/", "subreddit_subscribers": 55194, "created_utc": 1589922820.0, "num_crossposts": 2, "media": null, "is_video": false}}, {"kind": "t3", "data": {"approved_at_utc": null, "subreddit": "haskell", "selftext": "", "author_fullname": "t2_3qjdu", "saved": false, "mod_reason_title": null, "gilded": 0, "clicked": false, "title": "DerivingVia sums-of-products", "link_flair_richtext": [], "subreddit_name_prefixed": "r/haskell", "hidden": false, "pwls": 6, "link_flair_css_class": null, "downs": 0, "hide_score": false, "name": "t3_gn8c5r", "quarantine": false, "link_flair_text_color": "dark", "upvote_ratio": 1.0, "author_flair_background_color": null, "subreddit_type": "public", "ups": 17, "total_awards_received": 0, "media_embed": {}, "author_flair_template_id": null, "is_original_content": false, "user_reports": [], "secure_media": null, "is_reddit_media_domain": false, "is_meta": false, "category": null, "secure_media_embed": {}, "link_flair_text": null, "can_mod_post": false, "score": 17, "approved_by": null, "author_premium": false, "thumbnail": "", "edited": false, "author_flair_css_class": null, "author_flair_richtext": [], "gildings": {}, "content_categories": null, "is_self": false, "mod_note": null, "created": 1589996118.0, "link_flair_type": "text", "wls": 6, "removed_by_category": null, "banned_by": null, "author_flair_type": "text", "domain": "iceland_jack.brick.do", "allow_live_comments": false, "selftext_html": null, "likes": null, "suggested_sort": null, "banned_at_utc": null, "view_count": null, "archived": false, "no_follow": false, "is_crosspostable": false, "pinned": false, "over_18": false, "all_awardings": [], "awarders": [], "media_only": false, "can_gild": false, "spoiler": false, "locked": false, "author_flair_text": null, "treatment_tags": [], "visited": false, "removed_by": null, "num_reports": null, "distinguished": null, "subreddit_id": "t5_2qh36", "mod_reason_by": null, "removal_reason": null, "link_flair_background_color": "", "id": "gn8c5r", "is_robot_indexable": true, "report_reasons": null, "author": "Iceland_jack", "discussion_type": null, "num_comments": 5, "send_replies": true, "whitelist_status": "all_ads", "contest_mode": false, "mod_reports": [], "author_patreon_flair": false, "author_flair_text_color": null, "permalink": "/r/haskell/comments/gn8c5r/derivingvia_sumsofproducts/", "parent_whitelist_status": "all_ads", "stickied": false, "url": "https://iceland_jack.brick.do/e28e745c-40b8-4b0b-8148-1f1ae0c32d43", "subreddit_subscribers": 55194, "created_utc": 1589967318.0, "num_crossposts": 0, "media": null, "is_video": false}}, {"kind": "t3", "data": {"approved_at_utc": null, "subreddit": "haskell", "selftext": "", "author_fullname": "t2_jxviuup", "saved": false, "mod_reason_title": null, "gilded": 0, "clicked": false, "title": "Alejandro Serrano Mena on Why Functors and Applicatives Compose but Monads Don't", "link_flair_richtext": [], "subreddit_name_prefixed": "r/haskell", "hidden": false, "pwls": 6, "link_flair_css_class": null, "downs": 0, "hide_score": false, "name": "t3_gn2tqs", "quarantine": false, "link_flair_text_color": "dark", "upvote_ratio": 0.95, "author_flair_background_color": null, "subreddit_type": "public", "ups": 47, "total_awards_received": 0, "media_embed": {"content": "&lt;iframe width=\"600\" height=\"338\" src=\"https://www.youtube.com/embed/eZ9FpG8May8?feature=oembed&amp;enablejsapi=1\" frameborder=\"0\" allow=\"accelerometer; autoplay; encrypted-media; gyroscope; picture-in-picture\" allowfullscreen&gt;&lt;/iframe&gt;", "width": 600, "scrolling": false, "height": 338}, "author_flair_template_id": null, "is_original_content": false, "user_reports": [], "secure_media": {"type": "youtube.com", "oembed": {"provider_url": "https://www.youtube.com/", "version": "1.0", "title": "Alejandro Serrano Mena on Why Functors and Applicatives Compose but Monads Don't", "type": "video", "thumbnail_width": 480, "height": 338, "width": 600, "html": "&lt;iframe width=\"600\" height=\"338\" src=\"https://www.youtube.com/embed/eZ9FpG8May8?feature=oembed&amp;enablejsapi=1\" frameborder=\"0\" allow=\"accelerometer; autoplay; encrypted-media; gyroscope; picture-in-picture\" allowfullscreen&gt;&lt;/iframe&gt;", "author_name": "Berlin Functional Programming Group", "provider_name": "YouTube", "thumbnail_url": "https://i.ytimg.com/vi/eZ9FpG8May8/hqdefault.jpg", "thumbnail_height": 360, "author_url": "https://www.youtube.com/channel/UCNp-DVb8cQRIOo32sZhWgNg"}}, "is_reddit_media_domain": false, "is_meta": false, "category": null, "secure_media_embed": {"content": "&lt;iframe width=\"600\" height=\"338\" src=\"https://www.youtube.com/embed/eZ9FpG8May8?feature=oembed&amp;enablejsapi=1\" frameborder=\"0\" allow=\"accelerometer; autoplay; encrypted-media; gyroscope; picture-in-picture\" allowfullscreen&gt;&lt;/iframe&gt;", "width": 600, "scrolling": false, "media_domain_url": "https://www.redditmedia.com/mediaembed/gn2tqs", "height": 338}, "link_flair_text": null, "can_mod_post": false, "score": 47, "approved_by": null, "author_premium": false, "thumbnail": "", "edited": false, "author_flair_css_class": null, "author_flair_richtext": [], "gildings": {}, "content_categories": null, "is_self": false, "mod_note": null, "created": 1589970172.0, "link_flair_type": "text", "wls": 6, "removed_by_category": null, "banned_by": null, "author_flair_type": "text", "domain": "youtube.com", "allow_live_comments": false, "selftext_html": null, "likes": null, "suggested_sort": null, "banned_at_utc": null, "view_count": null, "archived": false, "no_follow": false, "is_crosspostable": false, "pinned": false, "over_18": false, "all_awardings": [], "awarders": [], "media_only": false, "can_gild": false, "spoiler": false, "locked": false, "author_flair_text": null, "treatment_tags": [], "visited": false, "removed_by": null, "num_reports": null, "distinguished": null, "subreddit_id": "t5_2qh36", "mod_reason_by": null, "removal_reason": null, "link_flair_background_color": "", "id": "gn2tqs", "is_robot_indexable": true, "report_reasons": null, "author": "iedoub", "discussion_type": null, "num_comments": 5, "send_replies": true, "whitelist_status": "all_ads", "contest_mode": false, "mod_reports": [], "author_patreon_flair": false, "author_flair_text_color": null, "permalink": "/r/haskell/comments/gn2tqs/alejandro_serrano_mena_on_why_functors_and/", "parent_whitelist_status": "all_ads", "stickied": false, "url": "https://www.youtube.com/watch?v=eZ9FpG8May8&amp;feature=youtu.be", "subreddit_subscribers": 55194, "created_utc": 1589941372.0, "num_crossposts": 0, "media": {"type": "youtube.com", "oembed": {"provider_url": "https://www.youtube.com/", "version": "1.0", "title": "Alejandro Serrano Mena on Why Functors and Applicatives Compose but Monads Don't", "type": "video", "thumbnail_width": 480, "height": 338, "width": 600, "html": "&lt;iframe width=\"600\" height=\"338\" src=\"https://www.youtube.com/embed/eZ9FpG8May8?feature=oembed&amp;enablejsapi=1\" frameborder=\"0\" allow=\"accelerometer; autoplay; encrypted-media; gyroscope; picture-in-picture\" allowfullscreen&gt;&lt;/iframe&gt;", "author_name": "Berlin Functional Programming Group", "provider_name": "YouTube", "thumbnail_url": "https://i.ytimg.com/vi/eZ9FpG8May8/hqdefault.jpg", "thumbnail_height": 360, "author_url": "https://www.youtube.com/channel/UCNp-DVb8cQRIOo32sZhWgNg"}}, "is_video": false}}, {"kind": "t3", "data": {"approved_at_utc": null, "subreddit": "haskell", "selftext": "Saw a thread asking what Haskell is good for. I'm wondering now if it would be more interesting to hear what Haskell isn't good for.\n\nBy \"bad for\" I mean practically speaking given the current availability of ecosystem: libraries, tools, compiler extensions, devs, etc, etc. And, of course, if Haskell isn't good for something theoretically then it won't be good for it practically, so that's interesting too", "author_fullname": "t2_f4gx2", "saved": false, "mod_reason_title": null, "gilded": 0, "clicked": false, "title": "What is Haskell bad for?", "link_flair_richtext": [], "subreddit_name_prefixed": "r/haskell", "hidden": false, "pwls": 6, "link_flair_css_class": null, "downs": 0, "hide_score": false, "name": "t3_gmxsp4", "quarantine": false, "link_flair_text_color": "dark", "upvote_ratio": 0.94, "author_flair_background_color": null, "subreddit_type": "public", "ups": 26, "total_awards_received": 0, "media_embed": {}, "author_flair_template_id": null, "is_original_content": false, "user_reports": [], "secure_media": null, "is_reddit_media_domain": false, "is_meta": false, "category": null, "secure_media_embed": {}, "link_flair_text": null, "can_mod_post": false, "score": 26, "approved_by": null, "author_premium": false, "thumbnail": "", "edited": false, "author_flair_css_class": null, "author_flair_richtext": [], "gildings": {}, "content_categories": null, "is_self": true, "mod_note": null, "created": 1589952776.0, "link_flair_type": "text", "wls": 6, "removed_by_category": null, "banned_by": null, "author_flair_type": "text", "domain": "self.haskell", "allow_live_comments": false, "selftext_html": "&lt;!-- SC_OFF --&gt;&lt;div class=\"md\"&gt;&lt;p&gt;Saw a thread asking what Haskell is good for. I&amp;#39;m wondering now if it would be more interesting to hear what Haskell isn&amp;#39;t good for.&lt;/p&gt;\n\n&lt;p&gt;By &amp;quot;bad for&amp;quot; I mean practically speaking given the current availability of ecosystem: libraries, tools, compiler extensions, devs, etc, etc. And, of course, if Haskell isn&amp;#39;t good for something theoretically then it won&amp;#39;t be good for it practically, so that&amp;#39;s interesting too&lt;/p&gt;\n&lt;/div&gt;&lt;!-- SC_ON --&gt;", "likes": null, "suggested_sort": null, "banned_at_utc": null, "view_count": null, "archived": false, "no_follow": false, "is_crosspostable": false, "pinned": false, "over_18": false, "all_awardings": [], "awarders": [], "media_only": false, "can_gild": false, "spoiler": false, "locked": false, "author_flair_text": null, "treatment_tags": [], "visited": false, "removed_by": null, "num_reports": null, "distinguished": null, "subreddit_id": "t5_2qh36", "mod_reason_by": null, "removal_reason": null, "link_flair_background_color": "", "id": "gmxsp4", "is_robot_indexable": true, "report_reasons": null, "author": "Dekans", "discussion_type": null, "num_comments": 65, "send_replies": true, "whitelist_status": "all_ads", "contest_mode": false, "mod_reports": [], "author_patreon_flair": false, "author_flair_text_color": null, "permalink": "/r/haskell/comments/gmxsp4/what_is_haskell_bad_for/", "parent_whitelist_status": "all_ads", "stickied": false, "url": "https://old.reddit.com/r/haskell/comments/gmxsp4/what_is_haskell_bad_for/", "subreddit_subscribers": 55194, "created_utc": 1589923976.0, "num_crossposts": 0, "media": null, "is_video": false}}, {"kind": "t3", "data": {"approved_at_utc": null, "subreddit": "haskell", "selftext": "", "author_fullname": "t2_jxviuup", "saved": false, "mod_reason_title": null, "gilded": 0, "clicked": false, "title": "Benjamin Pierce: Backtracking Generators for Random Testing", "link_flair_richtext": [], "subreddit_name_prefixed": "r/haskell", "hidden": false, "pwls": 6, "link_flair_css_class": null, "downs": 0, "hide_score": false, "name": "t3_gmlw3d", "quarantine": false, "link_flair_text_color": "dark", "upvote_ratio": 0.94, "author_flair_background_color": null, "subreddit_type": "public", "ups": 61, "total_awards_received": 0, "media_embed": {}, "author_flair_template_id": null, "is_original_content": false, "user_reports": [], "secure_media": null, "is_reddit_media_domain": false, "is_meta": false, "category": null, "secure_media_embed": {}, "link_flair_text": null, "can_mod_post": false, "score": 61, "approved_by": null, "author_premium": false, "thumbnail": "", "edited": false, "author_flair_css_class": null, "author_flair_richtext": [], "gildings": {}, "content_categories": null, "is_self": false, "mod_note": null, "created": 1589912401.0, "link_flair_type": "text", "wls": 6, "removed_by_category": null, "banned_by": null, "author_flair_type": "text", "domain": "youtube.com", "allow_live_comments": false, "selftext_html": null, "likes": null, "suggested_sort": null, "banned_at_utc": null, "view_count": null, "archived": false, "no_follow": false, "is_crosspostable": false, "pinned": false, "over_18": false, "all_awardings": [], "awarders": [], "media_only": false, "can_gild": false, "spoiler": false, "locked": false, "author_flair_text": null, "treatment_tags": [], "visited": false, "removed_by": null, "num_reports": null, "distinguished": null, "subreddit_id": "t5_2qh36", "mod_reason_by": null, "removal_reason": null, "link_flair_background_color": "", "id": "gmlw3d", "is_robot_indexable": true, "report_reasons": null, "author": "iedoub", "discussion_type": null, "num_comments": 2, "send_replies": true, "whitelist_status": "all_ads", "contest_mode": false, "mod_reports": [], "author_patreon_flair": false, "author_flair_text_color": null, "permalink": "/r/haskell/comments/gmlw3d/benjamin_pierce_backtracking_generators_for/", "parent_whitelist_status": "all_ads", "stickied": false, "url": "https://www.youtube.com/watch?v=dfZ94N0hS4I&amp;feature=youtu.be", "subreddit_subscribers": 55194, "created_utc": 1589883601.0, "num_crossposts": 0, "media": null, "is_video": false}}, {"kind": "t3", "data": {"approved_at_utc": null, "subreddit": "haskell", "selftext": "", "author_fullname": "t2_2zl2", "saved": false, "mod_reason_title": null, "gilded": 0, "clicked": false, "title": "Haskenthetical - another take on \"Haskell with a Lisp syntax\"", "link_flair_richtext": [], "subreddit_name_prefixed": "r/haskell", "hidden": false, "pwls": 6, "link_flair_css_class": null, "downs": 0, "hide_score": false, "name": "t3_gmybcf", "quarantine": false, "link_flair_text_color": "dark", "upvote_ratio": 1.0, "author_flair_background_color": null, "subreddit_type": "public", "ups": 5, "total_awards_received": 0, "media_embed": {}, "author_flair_template_id": null, "is_original_content": false, "user_reports": [], "secure_media": null, "is_reddit_media_domain": false, "is_meta": false, "category": null, "secure_media_embed": {}, "link_flair_text": null, "can_mod_post": false, "score": 5, "approved_by": null, "author_premium": false, "thumbnail": "", "edited": false, "author_flair_css_class": null, "author_flair_richtext": [], "gildings": {}, "content_categories": null, "is_self": false, "mod_note": null, "created": 1589954453.0, "link_flair_type": "text", "wls": 6, "removed_by_category": null, "banned_by": null, "author_flair_type": "text", "domain": "reasonableapproximation.net", "allow_live_comments": false, "selftext_html": null, "likes": null, "suggested_sort": null, "banned_at_utc": null, "view_count": null, "archived": false, "no_follow": false, "is_crosspostable": false, "pinned": false, "over_18": false, "all_awardings": [], "awarders": [], "media_only": false, "can_gild": false, "spoiler": false, "locked": false, "author_flair_text": null, "treatment_tags": [], "visited": false, "removed_by": null, "num_reports": null, "distinguished": null, "subreddit_id": "t5_2qh36", "mod_reason_by": null, "removal_reason": null, "link_flair_background_color": "", "id": "gmybcf", "is_robot_indexable": true, "report_reasons": null, "author": "philh", "discussion_type": null, "num_comments": 2, "send_replies": true, "whitelist_status": "all_ads", "contest_mode": false, "mod_reports": [], "author_patreon_flair": false, "author_flair_text_color": null, "permalink": "/r/haskell/comments/gmybcf/haskenthetical_another_take_on_haskell_with_a/", "parent_whitelist_status": "all_ads", "stickied": false, "url": "http://reasonableapproximation.net/2020/05/19/haskenthetical.html", "subreddit_subscribers": 55194, "created_utc": 1589925653.0, "num_crossposts": 0, "media": null, "is_video": false}}, {"kind": "t3", "data": {"approved_at_utc": null, "subreddit": "haskell", "selftext": "", "author_fullname": "t2_4hurx", "saved": false, "mod_reason_title": null, "gilded": 0, "clicked": false, "title": "How to define JSON instances quickly", "link_flair_richtext": [], "subreddit_name_prefixed": "r/haskell", "hidden": false, "pwls": 6, "link_flair_css_class": null, "downs": 0, "hide_score": false, "name": "t3_gmmp65", "quarantine": false, "link_flair_text_color": "dark", "upvote_ratio": 0.96, "author_flair_background_color": null, "subreddit_type": "public", "ups": 24, "total_awards_received": 0, "media_embed": {}, "author_flair_template_id": null, "is_original_content": false, "user_reports": [], "secure_media": null, "is_reddit_media_domain": false, "is_meta": false, "category": null, "secure_media_embed": {}, "link_flair_text": null, "can_mod_post": false, "score": 24, "approved_by": null, "author_premium": false, "thumbnail": "", "edited": false, "author_flair_css_class": null, "author_flair_richtext": [], "gildings": {}, "content_categories": null, "is_self": false, "mod_note": null, "created": 1589916349.0, "link_flair_type": "text", "wls": 6, "removed_by_category": null, "banned_by": null, "author_flair_type": "text", "domain": "dev.to", "allow_live_comments": false, "selftext_html": null, "likes": null, "suggested_sort": null, "banned_at_utc": null, "view_count": null, "archived": false, "no_follow": false, "is_crosspostable": false, "pinned": false, "over_18": false, "all_awardings": [], "awarders": [], "media_only": false, "can_gild": false, "spoiler": false, "locked": false, "author_flair_text": null, "treatment_tags": [], "visited": false, "removed_by": null, "num_reports": null, "distinguished": null, "subreddit_id": "t5_2qh36", "mod_reason_by": null, "removal_reason": null, "link_flair_background_color": "", "id": "gmmp65", "is_robot_indexable": true, "report_reasons": null, "author": "taylorfausak", "discussion_type": null, "num_comments": 9, "send_replies": true, "whitelist_status": "all_ads", "contest_mode": false, "mod_reports": [], "author_patreon_flair": false, "author_flair_text_color": null, "permalink": "/r/haskell/comments/gmmp65/how_to_define_json_instances_quickly/", "parent_whitelist_status": "all_ads", "stickied": false, "url": "https://dev.to/tfausak/how-to-define-json-instances-quickly-5ei7", "subreddit_subscribers": 55194, "created_utc": 1589887549.0, "num_crossposts": 0, "media": null, "is_video": false}}, {"kind": "t3", "data": {"approved_at_utc": null, "subreddit": "haskell", "selftext": "I try to manage my packages by nix, but the following command `nix-env -iA nixpkgs.stack` do not create a `.stack` folder for me, and then run stack global will throw exception like this.\n\n```shell\n$ stack ghci  \nopenAnonymousTempFileFromDir: inappropriate type (Is a directory)\n```", "author_fullname": "t2_22yozddx", "saved": false, "mod_reason_title": null, "gilded": 0, "clicked": false, "title": "Stack installed by nix seems do not create `.stack` folder under home dir properly.", "link_flair_richtext": [], "subreddit_name_prefixed": "r/haskell", "hidden": false, "pwls": 6, "link_flair_css_class": null, "downs": 0, "hide_score": false, "name": "t3_gn3vhr", "quarantine": false, "link_flair_text_color": "dark", "upvote_ratio": 0.5, "author_flair_background_color": null, "subreddit_type": "public", "ups": 0, "total_awards_received": 0, "media_embed": {}, "author_flair_template_id": null, "is_original_content": false, "user_reports": [], "secure_media": null, "is_reddit_media_domain": false, "is_meta": false, "category": null, "secure_media_embed": {}, "link_flair_text": null, "can_mod_post": false, "score": 0, "approved_by": null, "author_premium": false, "thumbnail": "", "edited": false, "author_flair_css_class": null, "author_flair_richtext": [], "gildings": {}, "content_categories": null, "is_self": true, "mod_note": null, "created": 1589974381.0, "link_flair_type": "text", "wls": 6, "removed_by_category": null, "banned_by": null, "author_flair_type": "text", "domain": "self.haskell", "allow_live_comments": false, "selftext_html": "&lt;!-- SC_OFF --&gt;&lt;div class=\"md\"&gt;&lt;p&gt;I try to manage my packages by nix, but the following command &lt;code&gt;nix-env -iA nixpkgs.stack&lt;/code&gt; do not create a &lt;code&gt;.stack&lt;/code&gt; folder for me, and then run stack global will throw exception like this.&lt;/p&gt;\n\n&lt;p&gt;&lt;code&gt;shell\n$ stack ghci  \nopenAnonymousTempFileFromDir: inappropriate type (Is a directory)\n&lt;/code&gt;&lt;/p&gt;\n&lt;/div&gt;&lt;!-- SC_ON --&gt;", "likes": null, "suggested_sort": null, "banned_at_utc": null, "view_count": null, "archived": false, "no_follow": true, "is_crosspostable": false, "pinned": false, "over_18": false, "all_awardings": [], "awarders": [], "media_only": false, "can_gild": false, "spoiler": false, "locked": false, "author_flair_text": null, "treatment_tags": [], "visited": false, "removed_by": null, "num_reports": null, "distinguished": null, "subreddit_id": "t5_2qh36", "mod_reason_by": null, "removal_reason": null, "link_flair_background_color": "", "id": "gn3vhr", "is_robot_indexable": true, "report_reasons": null, "author": "wangqiao11", "discussion_type": null, "num_comments": 3, "send_replies": true, "whitelist_status": "all_ads", "contest_mode": false, "mod_reports": [], "author_patreon_flair": false, "author_flair_text_color": null, "permalink": "/r/haskell/comments/gn3vhr/stack_installed_by_nix_seems_do_not_create_stack/", "parent_whitelist_status": "all_ads", "stickied": false, "url": "https://old.reddit.com/r/haskell/comments/gn3vhr/stack_installed_by_nix_seems_do_not_create_stack/", "subreddit_subscribers": 55194, "created_utc": 1589945581.0, "num_crossposts": 0, "media": null, "is_video": false}}, {"kind": "t3", "data": {"approved_at_utc": null, "subreddit": "haskell", "selftext": "I've been beating my head against this issue for a while and thought maybe someone here has a good idea of how to approach this problem.   \nI'm working on a program which has a simple terminal GUI interface using [brick](https://github.com/jtdaugherty/brick), and now I want to be able to run SMT queries in the program using the [SBV](https://hackage.haskell.org/package/sbv-8.6) library. The problem is that the interaction between the program and the SMT solver is being tracked in a monad context (\\`[MonadQuery](https://hackage.haskell.org/package/sbv-8.6/docs/src/Data.SBV.Core.Symbolic.html#MonadQuery)\\`, \\`Query a\\` or \\`Symbolic a\\`), while the event handling monad \\`[EventM n a](https://github.com/jtdaugherty/brick/blob/758d8138301ce521214247bd9190abbff7ec0f3d/src/Brick/Types.hs#L128)\\` of brick seems to only allow IO actions.  \n\n\nHow would I best go about unifying these contexts? Is there a way to generalize the event handling of brick to allow for other types of monadic actions to be performed? Or should I rather try to save the state that defines the \\`MonadQuery\\` of SBV in the application state? I found no good way of \"saving\" the context of a MonadQuery to be able to \"resume\" it a later time.", "author_fullname": "t2_cx67k", "saved": false, "mod_reason_title": null, "gilded": 0, "clicked": false, "title": "Combining Brick and SBV monadic contexts", "link_flair_richtext": [], "subreddit_name_prefixed": "r/haskell", "hidden": false, "pwls": 6, "link_flair_css_class": null, "downs": 0, "hide_score": false, "name": "t3_gmn78x", "quarantine": false, "link_flair_text_color": "dark", "upvote_ratio": 1.0, "author_flair_background_color": null, "subreddit_type": "public", "ups": 9, "total_awards_received": 0, "media_embed": {}, "author_flair_template_id": null, "is_original_content": false, "user_reports": [], "secure_media": null, "is_reddit_media_domain": false, "is_meta": false, "category": null, "secure_media_embed": {}, "link_flair_text": null, "can_mod_post": false, "score": 9, "approved_by": null, "author_premium": false, "thumbnail": "", "edited": false, "author_flair_css_class": null, "author_flair_richtext": [], "gildings": {}, "content_categories": null, "is_self": true, "mod_note": null, "created": 1589918474.0, "link_flair_type": "text", "wls": 6, "removed_by_category": null, "banned_by": null, "author_flair_type": "text", "domain": "self.haskell", "allow_live_comments": false, "selftext_html": "&lt;!-- SC_OFF --&gt;&lt;div class=\"md\"&gt;&lt;p&gt;I&amp;#39;ve been beating my head against this issue for a while and thought maybe someone here has a good idea of how to approach this problem.&lt;br/&gt;\nI&amp;#39;m working on a program which has a simple terminal GUI interface using &lt;a href=\"https://github.com/jtdaugherty/brick\"&gt;brick&lt;/a&gt;, and now I want to be able to run SMT queries in the program using the &lt;a href=\"https://hackage.haskell.org/package/sbv-8.6\"&gt;SBV&lt;/a&gt; library. The problem is that the interaction between the program and the SMT solver is being tracked in a monad context (`&lt;a href=\"https://hackage.haskell.org/package/sbv-8.6/docs/src/Data.SBV.Core.Symbolic.html#MonadQuery\"&gt;MonadQuery&lt;/a&gt;`, `Query a` or `Symbolic a`), while the event handling monad `&lt;a href=\"https://github.com/jtdaugherty/brick/blob/758d8138301ce521214247bd9190abbff7ec0f3d/src/Brick/Types.hs#L128\"&gt;EventM n a&lt;/a&gt;` of brick seems to only allow IO actions.  &lt;/p&gt;\n\n&lt;p&gt;How would I best go about unifying these contexts? Is there a way to generalize the event handling of brick to allow for other types of monadic actions to be performed? Or should I rather try to save the state that defines the `MonadQuery` of SBV in the application state? I found no good way of &amp;quot;saving&amp;quot; the context of a MonadQuery to be able to &amp;quot;resume&amp;quot; it a later time.&lt;/p&gt;\n&lt;/div&gt;&lt;!-- SC_ON --&gt;", "likes": null, "suggested_sort": null, "banned_at_utc": null, "view_count": null, "archived": false, "no_follow": false, "is_crosspostable": false, "pinned": false, "over_18": false, "all_awardings": [], "awarders": [], "media_only": false, "can_gild": false, "spoiler": false, "locked": false, "author_flair_text": null, "treatment_tags": [], "visited": false, "removed_by": null, "num_reports": null, "distinguished": null, "subreddit_id": "t5_2qh36", "mod_reason_by": null, "removal_reason": null, "link_flair_background_color": "", "id": "gmn78x", "is_robot_indexable": true, "report_reasons": null, "author": "Scentable", "discussion_type": null, "num_comments": 5, "send_replies": true, "whitelist_status": "all_ads", "contest_mode": false, "mod_reports": [], "author_patreon_flair": false, "author_flair_text_color": null, "permalink": "/r/haskell/comments/gmn78x/combining_brick_and_sbv_monadic_contexts/", "parent_whitelist_status": "all_ads", "stickied": false, "url": "https://old.reddit.com/r/haskell/comments/gmn78x/combining_brick_and_sbv_monadic_contexts/", "subreddit_subscribers": 55194, "created_utc": 1589889674.0, "num_crossposts": 0, "media": null, "is_video": false}}, {"kind": "t3", "data": {"approved_at_utc": null, "subreddit": "haskell", "selftext": "", "author_fullname": "t2_fr9sxjo", "saved": false, "mod_reason_title": null, "gilded": 0, "clicked": false, "title": "I am having difficulty installing Haskero for VSCode", "link_flair_richtext": [], "subreddit_name_prefixed": "r/haskell", "hidden": false, "pwls": 6, "link_flair_css_class": null, "downs": 0, "hide_score": false, "name": "t3_gmte13", "quarantine": false, "link_flair_text_color": "dark", "upvote_ratio": 0.75, "author_flair_background_color": null, "subreddit_type": "public", "ups": 4, "total_awards_received": 0, "media_embed": {}, "author_flair_template_id": null, "is_original_content": false, "user_reports": [], "secure_media": null, "is_reddit_media_domain": false, "is_meta": false, "category": null, "secure_media_embed": {}, "link_flair_text": null, "can_mod_post": false, "score": 4, "approved_by": null, "author_premium": false, "thumbnail": "", "edited": false, "author_flair_css_class": null, "author_flair_richtext": [], "gildings": {}, "content_categories": null, "is_self": false, "mod_note": null, "crosspost_parent_list": [{"approved_at_utc": null, "subreddit": "vscode", "selftext": "I am currently trying to install Haskero for VSCode. I am using [this link](https://gitlab.com/vannnns/haskero/blob/master/client/doc/installation.md) and following the instructions, however I am stuck on step 5. Whenever I type\n\n    stack build intero --copy-compiler-tool\n\ninto the terminal, I get this error message:\n\n    Error: While constructing the build plan, the following exceptions were encountered:\n    \n    In the dependencies for intero-0.1.40:\n        ghc-8.8.3 from stack configuration does not match &gt;=7.8 &amp;&amp; &lt;=8.6.5  (latest matching version is 8.6.5)\n    needed since intero is a build target.\n    \n    Some different approaches to resolving this:\n    \n      * Set 'allow-newer: true' in C:\\sr\\config.yaml to ignore all version constraints and build anyway.\n    \n      * Recommended action: try adding the following to your extra-deps in C:\\sr\\global-project\\stack.yaml:\n    \n    - ghc-8.6.5@sha256:3591225289bdf8cf8f62b10f2aebc9ea3e25a15294545a5312a419e0317784f9,13976\n    \n    Plan construction failed.\n\nI do not know how to handle this. Any  suggestions? Thank you in advance.", "author_fullname": "t2_fr9sxjo", "saved": false, "mod_reason_title": null, "gilded": 0, "clicked": false, "title": "I am having difficulty installing Haskero.", "link_flair_richtext": [], "subreddit_name_prefixed": "r/vscode", "hidden": false, "pwls": 6, "link_flair_css_class": null, "downs": 0, "hide_score": false, "name": "t3_gm53c8", "quarantine": false, "link_flair_text_color": "dark", "upvote_ratio": 0.72, "author_flair_background_color": null, "subreddit_type": "public", "ups": 3, "total_awards_received": 0, "media_embed": {}, "author_flair_template_id": null, "is_original_content": true, "user_reports": [], "secure_media": null, "is_reddit_media_domain": false, "is_meta": false, "category": null, "secure_media_embed": {}, "link_flair_text": null, "can_mod_post": false, "score": 3, "approved_by": null, "author_premium": false, "thumbnail": "", "edited": false, "author_flair_css_class": null, "author_flair_richtext": [], "gildings": {}, "content_categories": null, "is_self": true, "mod_note": null, "created": 1589849248.0, "link_flair_type": "text", "wls": 6, "removed_by_category": null, "banned_by": null, "author_flair_type": "text", "domain": "self.vscode", "allow_live_comments": false, "selftext_html": "&lt;!-- SC_OFF --&gt;&lt;div class=\"md\"&gt;&lt;p&gt;I am currently trying to install Haskero for VSCode. I am using &lt;a href=\"https://gitlab.com/vannnns/haskero/blob/master/client/doc/installation.md\"&gt;this link&lt;/a&gt; and following the instructions, however I am stuck on step 5. Whenever I type&lt;/p&gt;\n\n&lt;pre&gt;&lt;code&gt;stack build intero --copy-compiler-tool\n&lt;/code&gt;&lt;/pre&gt;\n\n&lt;p&gt;into the terminal, I get this error message:&lt;/p&gt;\n\n&lt;pre&gt;&lt;code&gt;Error: While constructing the build plan, the following exceptions were encountered:\n\nIn the dependencies for intero-0.1.40:\n    ghc-8.8.3 from stack configuration does not match &amp;gt;=7.8 &amp;amp;&amp;amp; &amp;lt;=8.6.5  (latest matching version is 8.6.5)\nneeded since intero is a build target.\n\nSome different approaches to resolving this:\n\n  * Set &amp;#39;allow-newer: true&amp;#39; in C:\\sr\\config.yaml to ignore all version constraints and build anyway.\n\n  * Recommended action: try adding the following to your extra-deps in C:\\sr\\global-project\\stack.yaml:\n\n- ghc-8.6.5@sha256:3591225289bdf8cf8f62b10f2aebc9ea3e25a15294545a5312a419e0317784f9,13976\n\nPlan construction failed.\n&lt;/code&gt;&lt;/pre&gt;\n\n&lt;p&gt;I do not know how to handle this. Any  suggestions? Thank you in advance.&lt;/p&gt;\n&lt;/div&gt;&lt;!-- SC_ON --&gt;", "likes": null, "suggested_sort": null, "banned_at_utc": null, "view_count": null, "archived": false, "no_follow": false, "is_crosspostable": false, "pinned": false, "over_18": false, "all_awardings": [], "awarders": [], "media_only": false, "can_gild": false, "spoiler": false, "locked": false, "author_flair_text": null, "treatment_tags": [], "visited": false, "removed_by": null, "num_reports": null, "distinguished": null, "subreddit_id": "t5_381yu", "mod_reason_by": null, "removal_reason": null, "link_flair_background_color": "", "id": "gm53c8", "is_robot_indexable": true, "report_reasons": null, "author": "The-CPMills", "discussion_type": null, "num_comments": 0, "send_replies": true, "whitelist_status": "all_ads", "contest_mode": false, "mod_reports": [], "author_patreon_flair": false, "author_flair_text_color": null, "permalink": "/r/vscode/comments/gm53c8/i_am_having_difficulty_installing_haskero/", "parent_whitelist_status": "all_ads", "stickied": false, "url": "https://old.reddit.com/r/vscode/comments/gm53c8/i_am_having_difficulty_installing_haskero/", "subreddit_subscribers": 40653, "created_utc": 1589820448.0, "num_crossposts": 1, "media": null, "is_video": false}], "created": 1589939114.0, "link_flair_type": "text", "wls": 6, "removed_by_category": null, "banned_by": null, "author_flair_type": "text", "domain": "self.vscode", "allow_live_comments": false, "selftext_html": null, "likes": null, "suggested_sort": null, "banned_at_utc": null, "view_count": null, "archived": false, "no_follow": true, "is_crosspostable": false, "pinned": false, "over_18": false, "all_awardings": [], "awarders": [], "media_only": false, "can_gild": false, "spoiler": false, "locked": false, "author_flair_text": null, "treatment_tags": [], "visited": false, "removed_by": null, "num_reports": null, "distinguished": null, "subreddit_id": "t5_2qh36", "mod_reason_by": null, "removal_reason": null, "link_flair_background_color": "", "id": "gmte13", "is_robot_indexable": true, "report_reasons": null, "author": "The-CPMills", "discussion_type": null, "num_comments": 5, "send_replies": true, "whitelist_status": "all_ads", "contest_mode": false, "mod_reports": [], "author_patreon_flair": false, "crosspost_parent": "t3_gm53c8", "author_flair_text_color": null, "permalink": "/r/haskell/comments/gmte13/i_am_having_difficulty_installing_haskero_for/", "parent_whitelist_status": "all_ads", "stickied": false, "url": "/r/vscode/comments/gm53c8/i_am_having_difficulty_installing_haskero/", "subreddit_subscribers": 55194, "created_utc": 1589910314.0, "num_crossposts": 0, "media": null, "is_video": false}}, {"kind": "t3", "data": {"approved_at_utc": null, "subreddit": "haskell", "selftext": "", "author_fullname": "t2_7d9ta", "saved": false, "mod_reason_title": null, "gilded": 0, "clicked": false, "title": "[GHC Blog] The state of GHC on ARM", "link_flair_richtext": [], "subreddit_name_prefixed": "r/haskell", "hidden": false, "pwls": 6, "link_flair_css_class": null, "downs": 0, "hide_score": false, "name": "t3_gmbfyr", "quarantine": false, "link_flair_text_color": "dark", "upvote_ratio": 0.98, "author_flair_background_color": null, "subreddit_type": "public", "ups": 77, "total_awards_received": 0, "media_embed": {}, "author_flair_template_id": null, "is_original_content": false, "user_reports": [], "secure_media": null, "is_reddit_media_domain": false, "is_meta": false, "category": null, "secure_media_embed": {}, "link_flair_text": null, "can_mod_post": false, "score": 77, "approved_by": null, "author_premium": false, "thumbnail": "", "edited": false, "author_flair_css_class": null, "author_flair_richtext": [], "gildings": {}, "content_categories": null, "is_self": false, "mod_note": null, "created": 1589868527.0, "link_flair_type": "text", "wls": 6, "removed_by_category": null, "banned_by": null, "author_flair_type": "text", "domain": "haskell.org", "allow_live_comments": false, "selftext_html": null, "likes": null, "suggested_sort": null, "banned_at_utc": null, "view_count": null, "archived": false, "no_follow": false, "is_crosspostable": false, "pinned": false, "over_18": false, "all_awardings": [], "awarders": [], "media_only": false, "can_gild": false, "spoiler": false, "locked": false, "author_flair_text": null, "treatment_tags": [], "visited": false, "removed_by": null, "num_reports": null, "distinguished": null, "subreddit_id": "t5_2qh36", "mod_reason_by": null, "removal_reason": null, "link_flair_background_color": "", "id": "gmbfyr", "is_robot_indexable": true, "report_reasons": null, "author": "bgamari", "discussion_type": null, "num_comments": 9, "send_replies": true, "whitelist_status": "all_ads", "contest_mode": false, "mod_reports": [], "author_patreon_flair": false, "author_flair_text_color": null, "permalink": "/r/haskell/comments/gmbfyr/ghc_blog_the_state_of_ghc_on_arm/", "parent_whitelist_status": "all_ads", "stickied": false, "url": "https://www.haskell.org/ghc/blog/20200515-ghc-on-arm.html", "subreddit_subscribers": 55194, "created_utc": 1589839727.0, "num_crossposts": 1, "media": null, "is_video": false}}, {"kind": "t3", "data": {"approved_at_utc": null, "subreddit": "haskell", "selftext": "I'm trying to build the board for the Peg Solitaire game but I'm stuck. I hope you can help me. The following code runs and generates a square of 3 on 3 circles. How could I make 3 more such squares but put them in other positions? I use the Gloss library. \n\n&amp;#x200B;\n\n`module Main(main) where` \n\n`import Graphics.Gloss` \n\n`import Graphics.Gloss.Data.ViewPort` \n\n`import` [`Graphics.Gloss.Interface.Pure.Game`](https://Graphics.Gloss.Interface.Pure.Game)\n\n `import Data.List`  \n\n`width, height, offset :: Int` \n\n`width = 400` \n\n`height = 400`\n\n `offset = 100`  \n\n`window :: Display window = InWindow \"Peg Solitaire\" (width, height) (offset, offset)`\n\n  `background :: Color` \n\n`background = white`  \n\n`drawing :: Picture` \n\n`drawing = Pictures [ (translate (x * 40) (y * 40) $ circleSolid 12)| x&lt;-[-1..1], y&lt;-[2..4] ]`  \n\n`main = display window background drawing`", "author_fullname": "t2_tewbqxp", "saved": false, "mod_reason_title": null, "gilded": 0, "clicked": false, "title": "Drawing the game board in Haskell", "link_flair_richtext": [], "subreddit_name_prefixed": "r/haskell", "hidden": false, "pwls": 6, "link_flair_css_class": null, "downs": 0, "hide_score": false, "name": "t3_gmsipz", "quarantine": false, "link_flair_text_color": "dark", "upvote_ratio": 0.67, "author_flair_background_color": null, "subreddit_type": "public", "ups": 2, "total_awards_received": 0, "media_embed": {}, "author_flair_template_id": null, "is_original_content": false, "user_reports": [], "secure_media": null, "is_reddit_media_domain": false, "is_meta": false, "category": null, "secure_media_embed": {}, "link_flair_text": null, "can_mod_post": false, "score": 2, "approved_by": null, "author_premium": false, "thumbnail": "", "edited": false, "author_flair_css_class": null, "author_flair_richtext": [], "gildings": {}, "content_categories": null, "is_self": true, "mod_note": null, "created": 1589936485.0, "link_flair_type": "text", "wls": 6, "removed_by_category": null, "banned_by": null, "author_flair_type": "text", "domain": "self.haskell", "allow_live_comments": false, "selftext_html": "&lt;!-- SC_OFF --&gt;&lt;div class=\"md\"&gt;&lt;p&gt;I&amp;#39;m trying to build the board for the Peg Solitaire game but I&amp;#39;m stuck. I hope you can help me. The following code runs and generates a square of 3 on 3 circles. How could I make 3 more such squares but put them in other positions? I use the Gloss library. &lt;/p&gt;\n\n&lt;p&gt;&amp;#x200B;&lt;/p&gt;\n\n&lt;p&gt;&lt;code&gt;module Main(main) where&lt;/code&gt; &lt;/p&gt;\n\n&lt;p&gt;&lt;code&gt;import Graphics.Gloss&lt;/code&gt; &lt;/p&gt;\n\n&lt;p&gt;&lt;code&gt;import Graphics.Gloss.Data.ViewPort&lt;/code&gt; &lt;/p&gt;\n\n&lt;p&gt;&lt;code&gt;import&lt;/code&gt; &lt;a href=\"https://Graphics.Gloss.Interface.Pure.Game\"&gt;&lt;code&gt;Graphics.Gloss.Interface.Pure.Game&lt;/code&gt;&lt;/a&gt;&lt;/p&gt;\n\n&lt;p&gt;&lt;code&gt;import Data.List&lt;/code&gt;  &lt;/p&gt;\n\n&lt;p&gt;&lt;code&gt;width, height, offset :: Int&lt;/code&gt; &lt;/p&gt;\n\n&lt;p&gt;&lt;code&gt;width = 400&lt;/code&gt; &lt;/p&gt;\n\n&lt;p&gt;&lt;code&gt;height = 400&lt;/code&gt;&lt;/p&gt;\n\n&lt;p&gt;&lt;code&gt;offset = 100&lt;/code&gt;  &lt;/p&gt;\n\n&lt;p&gt;&lt;code&gt;window :: Display window = InWindow &amp;quot;Peg Solitaire&amp;quot; (width, height) (offset, offset)&lt;/code&gt;&lt;/p&gt;\n\n&lt;p&gt;&lt;code&gt;background :: Color&lt;/code&gt; &lt;/p&gt;\n\n&lt;p&gt;&lt;code&gt;background = white&lt;/code&gt;  &lt;/p&gt;\n\n&lt;p&gt;&lt;code&gt;drawing :: Picture&lt;/code&gt; &lt;/p&gt;\n\n&lt;p&gt;&lt;code&gt;drawing = Pictures [ (translate (x * 40) (y * 40) $ circleSolid 12)| x&amp;lt;-[-1..1], y&amp;lt;-[2..4] ]&lt;/code&gt;  &lt;/p&gt;\n\n&lt;p&gt;&lt;code&gt;main = display window background drawing&lt;/code&gt;&lt;/p&gt;\n&lt;/div&gt;&lt;!-- SC_ON --&gt;", "likes": null, "suggested_sort": null, "banned_at_utc": null, "view_count": null, "archived": false, "no_follow": true, "is_crosspostable": false, "pinned": false, "over_18": false, "all_awardings": [], "awarders": [], "media_only": false, "can_gild": false, "spoiler": false, "locked": false, "author_flair_text": null, "treatment_tags": [], "visited": false, "removed_by": null, "num_reports": null, "distinguished": null, "subreddit_id": "t5_2qh36", "mod_reason_by": null, "removal_reason": null, "link_flair_background_color": "", "id": "gmsipz", "is_robot_indexable": true, "report_reasons": null, "author": "radu23", "discussion_type": null, "num_comments": 11, "send_replies": true, "whitelist_status": "all_ads", "contest_mode": false, "mod_reports": [], "author_patreon_flair": false, "author_flair_text_color": null, "permalink": "/r/haskell/comments/gmsipz/drawing_the_game_board_in_haskell/", "parent_whitelist_status": "all_ads", "stickied": false, "url": "https://old.reddit.com/r/haskell/comments/gmsipz/drawing_the_game_board_in_haskell/", "subreddit_subscribers": 55194, "created_utc": 1589907685.0, "num_crossposts": 0, "media": null, "is_video": false}}, {"kind": "t3", "data": {"approved_at_utc": null, "subreddit": "haskell", "selftext": "", "author_fullname": "t2_jxviuup", "saved": false, "mod_reason_title": null, "gilded": 0, "clicked": false, "title": "Presentation on Purely Functional Data Structures - Donnacha Ois\u00edn Kidney", "link_flair_richtext": [], "subreddit_name_prefixed": "r/haskell", "hidden": false, "pwls": 6, "link_flair_css_class": null, "downs": 0, "hide_score": false, "name": "t3_gmen1i", "quarantine": false, "link_flair_text_color": "dark", "upvote_ratio": 0.95, "author_flair_background_color": null, "subreddit_type": "public", "ups": 25, "total_awards_received": 0, "media_embed": {}, "author_flair_template_id": null, "is_original_content": false, "user_reports": [], "secure_media": null, "is_reddit_media_domain": false, "is_meta": false, "category": null, "secure_media_embed": {}, "link_flair_text": null, "can_mod_post": false, "score": 25, "approved_by": null, "author_premium": false, "thumbnail": "", "edited": false, "author_flair_css_class": null, "author_flair_richtext": [], "gildings": {}, "content_categories": null, "is_self": false, "mod_note": null, "created": 1589879479.0, "link_flair_type": "text", "wls": 6, "removed_by_category": null, "banned_by": null, "author_flair_type": "text", "domain": "doisinkidney.com", "allow_live_comments": false, "selftext_html": null, "likes": null, "suggested_sort": null, "banned_at_utc": null, "view_count": null, "archived": false, "no_follow": false, "is_crosspostable": false, "pinned": false, "over_18": false, "all_awardings": [], "awarders": [], "media_only": false, "can_gild": false, "spoiler": false, "locked": false, "author_flair_text": null, "treatment_tags": [], "visited": false, "removed_by": null, "num_reports": null, "distinguished": null, "subreddit_id": "t5_2qh36", "mod_reason_by": null, "removal_reason": null, "link_flair_background_color": "", "id": "gmen1i", "is_robot_indexable": true, "report_reasons": null, "author": "iedoub", "discussion_type": null, "num_comments": 12, "send_replies": true, "whitelist_status": "all_ads", "contest_mode": false, "mod_reports": [], "author_patreon_flair": false, "author_flair_text_color": null, "permalink": "/r/haskell/comments/gmen1i/presentation_on_purely_functional_data_structures/", "parent_whitelist_status": "all_ads", "stickied": false, "url": "https://doisinkidney.com/posts/2020-05-19-purely-functional-data-structures-slides.html", "subreddit_subscribers": 55194, "created_utc": 1589850679.0, "num_crossposts": 0, "media": null, "is_video": false}}, {"kind": "t3", "data": {"approved_at_utc": null, "subreddit": "haskell", "selftext": "I created a project with stack. Most of the time during the project I used the .cabal file to add dependencies. And that worked fine. However when adding the dependency for a sat-solver I got the following error\n\n```\nminisat-solver needed, but the stack configuration has no specified version  (latest matching version\n               is 0.1)\n```\n\nTo solve this error I added the line\n\n```\n - minisat-solver-0.1@sha256:e2ff11b1ca8c66e43f8bb2e04f21bd1b812efb94ff215d74f998c928e7e92dcd,5210\n```\n\nto my .yaml file.\n\nNow whenever I use `stack build` I get the error\n\n```\n....cabal was modified manually Ignoring ...package.yaml in favor of the cabal file.\nIf you want to use the package.yaml file instead of the cabal file,\nthen please delete the cabal file.\n```\n\nHow should I solve this? Should I just delete the .cabal file? What changes should I make to .yaml file\n\n--\n\nThe .yaml flie\n\n```\n# This file was automatically generated by 'stack init'\n#\n# Some commonly used options have been documented as comments in this file.\n# For advanced use and comprehensive documentation of the format, please see:\n# https://docs.haskellstack.org/en/stable/yaml_configuration/\n\n# Resolver to choose a 'specific' stackage snapshot or a compiler version.\n# A snapshot resolver dictates the compiler version and the set of packages\n# to be used for project dependencies. For example:\n#\n# resolver: lts-3.5\n# resolver: nightly-2015-09-21\n# resolver: ghc-7.10.2\n#\n# The location of a snapshot can be provided as a file or url. Stack assumes\n# a snapshot provided as a file might change, whereas a url resource does not.\n#\n# resolver: ./custom-snapshot.yaml\n# resolver: https://example.com/snapshots/2018-01-01.yaml\nresolver: lts-14.20\n\n# User packages to be built.\n# Various formats can be used as shown in the example below.\n#\n# packages:\n# - some-directory\n# - https://example.com/foo/bar/baz-0.0.2.tar.gz\n#   subdirs:\n#   - auto-update\n#   - wai\npackages:\n- .\n# Dependency packages to be pulled from upstream that are not in the resolver.\n# These entries can reference officially published versions as well as\n# forks / in-progress versions pinned to a git hash. For example:\n#\n# extra-deps:\n# - acme-missiles-0.3\n# - git: https://github.com/commercialhaskell/stack.git\n#   commit: e7b331f14bcffb8367cd58fbfc8b40ec7642100a\n#\n# extra-deps: []\n\n# Override default flag values for local packages and extra-deps\n# flags: {}\n\n# Extra package databases containing global packages\n# extra-package-dbs: []\n\n# Control whether we use the GHC we find on the path\n# system-ghc: true\n#\n# Require a specific version of stack, using version ranges\n# require-stack-version: -any # Default\n# require-stack-version: \"&gt;=2.1\"\n#\n# Override the architecture used by stack, especially useful on Windows\n# arch: i386\n# arch: x86_64\n#\n# Extra directories used by stack for building\n# extra-include-dirs: [/path/to/dir]\n# extra-lib-dirs: [/path/to/dir]\n#\n# Allow a newer minor version of GHC than the snapshot specifies\n# compiler-check: newer-minor\n\nextra-deps:\n - minisat-solver-0.1@sha256:e2ff11b1ca8c66e43f8bb2e04f21bd1b812efb94ff215d74f998c928e7e92dcd,5210\n\n```\n\nThe cabal file\n\n```\ncabal-version: 1.12\n\n-- This file has been generated from package.yaml by hpack version 0.31.2.\n--\n-- see: https://github.com/sol/hpack\n--\n-- hash: 9e4c1b8d2c640f6364c7abf13e184823a0c4b7959a05310c93a9b6ff92efad16\n\nname:           dtl-model-checking\nversion:        0.1.0.0\ndescription:    Please see the README on GitHub at &lt;https://github.com/githubuser/dtl-model-checking#readme&gt;\nhomepage:       https://github.com/githubuser/dtl-model-checking#readme\nbug-reports:    https://github.com/githubuser/dtl-model-checking/issues\nauthor:         Author name here\nmaintainer:     example@example.com\ncopyright:      2020 Author name here\nlicense:        BSD3\nlicense-file:   LICENSE\nbuild-type:     Simple\nextra-source-files:\n    README.md\n    ChangeLog.md\n\nsource-repository head\n  type: git\n  location: https://github.com/githubuser/dtl-model-checking\n\nlibrary\n  exposed-modules:\n      Automaton\n      DTLFormula\n      AutomataTheoreticApproach\n      DTS\n      NBA\n      GNBA\n      Ielementary\n      CommonTypes\n      Utils\n      ExampleInstances\n      BMC\n  other-modules:\n      Paths_dtl_model_checking\n  hs-source-dirs:\n      src\n  build-depends:\n      base &gt;=4.7 &amp;&amp; &lt;5\n    , containers\n    , random\n    , minisat-solver &gt;= 0.1\n  default-language: Haskell2010\n\nexecutable dtl-model-checking-exe\n  main-is: Main.hs\n  other-modules:\n      Paths_dtl_model_checking\n  hs-source-dirs:\n      app\n  ghc-options: -O -threaded -rtsopts -with-rtsopts=-N\n  build-depends:\n      base &gt;=4.7 &amp;&amp; &lt;5\n    , dtl-model-checking\n    , containers\n    , random\n  default-language: Haskell2010\n\ntest-suite dtl-model-checking-test\n  type: exitcode-stdio-1.0\n  main-is: Spec.hs\n  other-modules:\n      Paths_dtl_model_checking\n  hs-source-dirs:\n      test\n  ghc-options: -O -threaded -rtsopts -with-rtsopts=-N\n  build-depends:\n      base &gt;=4.7 &amp;&amp; &lt;5\n    , dtl-model-checking\n    , containers\n    , hspec\n    , random\n  default-language: Haskell2010\n\nbenchmark dtl-model-checking-benchmark\n  type: exitcode-stdio-1.0 \n  main-is: Bench.hs\n  other-modules:\n      Paths_dtl_model_checking\n  hs-source-dirs:\n      benchmark\n  ghc-options: -O -threaded -fforce-recomp -rtsopts -with-rtsopts=-N\n  build-depends: base &gt;=4.7 &amp;&amp; &lt;5, dtl-model-checking, containers, criterion, random\n  default-language: Haskell2010\n```", "author_fullname": "t2_u7qgp4w", "saved": false, "mod_reason_title": null, "gilded": 0, "clicked": false, "title": "Error/warning on stack build", "link_flair_richtext": [], "subreddit_name_prefixed": "r/haskell", "hidden": false, "pwls": 6, "link_flair_css_class": null, "downs": 0, "hide_score": false, "name": "t3_gmoik7", "quarantine": false, "link_flair_text_color": "dark", "upvote_ratio": 0.5, "author_flair_background_color": null, "subreddit_type": "public", "ups": 0, "total_awards_received": 0, "media_embed": {}, "author_flair_template_id": null, "is_original_content": false, "user_reports": [], "secure_media": null, "is_reddit_media_domain": false, "is_meta": false, "category": null, "secure_media_embed": {}, "link_flair_text": null, "can_mod_post": false, "score": 0, "approved_by": null, "author_premium": false, "thumbnail": "", "edited": false, "author_flair_css_class": null, "author_flair_richtext": [], "gildings": {}, "content_categories": null, "is_self": true, "mod_note": null, "created": 1589923554.0, "link_flair_type": "text", "wls": 6, "removed_by_category": null, "banned_by": null, "author_flair_type": "text", "domain": "self.haskell", "allow_live_comments": false, "selftext_html": "&lt;!-- SC_OFF --&gt;&lt;div class=\"md\"&gt;&lt;p&gt;I created a project with stack. Most of the time during the project I used the .cabal file to add dependencies. And that worked fine. However when adding the dependency for a sat-solver I got the following error&lt;/p&gt;\n\n&lt;p&gt;&lt;code&gt;\nminisat-solver needed, but the stack configuration has no specified version  (latest matching version\n               is 0.1)\n&lt;/code&gt;&lt;/p&gt;\n\n&lt;p&gt;To solve this error I added the line&lt;/p&gt;\n\n&lt;p&gt;&lt;code&gt;\n - minisat-solver-0.1@sha256:e2ff11b1ca8c66e43f8bb2e04f21bd1b812efb94ff215d74f998c928e7e92dcd,5210\n&lt;/code&gt;&lt;/p&gt;\n\n&lt;p&gt;to my .yaml file.&lt;/p&gt;\n\n&lt;p&gt;Now whenever I use &lt;code&gt;stack build&lt;/code&gt; I get the error&lt;/p&gt;\n\n&lt;p&gt;&lt;code&gt;\n....cabal was modified manually Ignoring ...package.yaml in favor of the cabal file.\nIf you want to use the package.yaml file instead of the cabal file,\nthen please delete the cabal file.\n&lt;/code&gt;&lt;/p&gt;\n\n&lt;p&gt;How should I solve this? Should I just delete the .cabal file? What changes should I make to .yaml file&lt;/p&gt;\n\n&lt;h2&gt;&lt;/h2&gt;\n\n&lt;p&gt;The .yaml flie&lt;/p&gt;\n\n&lt;p&gt;```&lt;/p&gt;\n\n&lt;h1&gt;This file was automatically generated by &amp;#39;stack init&amp;#39;&lt;/h1&gt;\n\n&lt;h1&gt;Some commonly used options have been documented as comments in this file.&lt;/h1&gt;\n\n&lt;h1&gt;For advanced use and comprehensive documentation of the format, please see:&lt;/h1&gt;\n\n&lt;h1&gt;&lt;a href=\"https://docs.haskellstack.org/en/stable/yaml_configuration/\"&gt;https://docs.haskellstack.org/en/stable/yaml_configuration/&lt;/a&gt;&lt;/h1&gt;\n\n&lt;h1&gt;Resolver to choose a &amp;#39;specific&amp;#39; stackage snapshot or a compiler version.&lt;/h1&gt;\n\n&lt;h1&gt;A snapshot resolver dictates the compiler version and the set of packages&lt;/h1&gt;\n\n&lt;h1&gt;to be used for project dependencies. For example:&lt;/h1&gt;\n\n&lt;h1&gt;resolver: lts-3.5&lt;/h1&gt;\n\n&lt;h1&gt;resolver: nightly-2015-09-21&lt;/h1&gt;\n\n&lt;h1&gt;resolver: ghc-7.10.2&lt;/h1&gt;\n\n&lt;h1&gt;The location of a snapshot can be provided as a file or url. Stack assumes&lt;/h1&gt;\n\n&lt;h1&gt;a snapshot provided as a file might change, whereas a url resource does not.&lt;/h1&gt;\n\n&lt;h1&gt;resolver: ./custom-snapshot.yaml&lt;/h1&gt;\n\n&lt;h1&gt;resolver: &lt;a href=\"https://example.com/snapshots/2018-01-01.yaml\"&gt;https://example.com/snapshots/2018-01-01.yaml&lt;/a&gt;&lt;/h1&gt;\n\n&lt;p&gt;resolver: lts-14.20&lt;/p&gt;\n\n&lt;h1&gt;User packages to be built.&lt;/h1&gt;\n\n&lt;h1&gt;Various formats can be used as shown in the example below.&lt;/h1&gt;\n\n&lt;h1&gt;packages:&lt;/h1&gt;\n\n&lt;h1&gt;- some-directory&lt;/h1&gt;\n\n&lt;h1&gt;- &lt;a href=\"https://example.com/foo/bar/baz-0.0.2.tar.gz\"&gt;https://example.com/foo/bar/baz-0.0.2.tar.gz&lt;/a&gt;&lt;/h1&gt;\n\n&lt;h1&gt;subdirs:&lt;/h1&gt;\n\n&lt;h1&gt;- auto-update&lt;/h1&gt;\n\n&lt;h1&gt;- wai&lt;/h1&gt;\n\n&lt;p&gt;packages:\n- .&lt;/p&gt;\n\n&lt;h1&gt;Dependency packages to be pulled from upstream that are not in the resolver.&lt;/h1&gt;\n\n&lt;h1&gt;These entries can reference officially published versions as well as&lt;/h1&gt;\n\n&lt;h1&gt;forks / in-progress versions pinned to a git hash. For example:&lt;/h1&gt;\n\n&lt;h1&gt;extra-deps:&lt;/h1&gt;\n\n&lt;h1&gt;- acme-missiles-0.3&lt;/h1&gt;\n\n&lt;h1&gt;- git: &lt;a href=\"https://github.com/commercialhaskell/stack.git\"&gt;https://github.com/commercialhaskell/stack.git&lt;/a&gt;&lt;/h1&gt;\n\n&lt;h1&gt;commit: e7b331f14bcffb8367cd58fbfc8b40ec7642100a&lt;/h1&gt;\n\n&lt;h1&gt;extra-deps: []&lt;/h1&gt;\n\n&lt;h1&gt;Override default flag values for local packages and extra-deps&lt;/h1&gt;\n\n&lt;h1&gt;flags: {}&lt;/h1&gt;\n\n&lt;h1&gt;Extra package databases containing global packages&lt;/h1&gt;\n\n&lt;h1&gt;extra-package-dbs: []&lt;/h1&gt;\n\n&lt;h1&gt;Control whether we use the GHC we find on the path&lt;/h1&gt;\n\n&lt;h1&gt;system-ghc: true&lt;/h1&gt;\n\n&lt;h1&gt;Require a specific version of stack, using version ranges&lt;/h1&gt;\n\n&lt;h1&gt;require-stack-version: -any # Default&lt;/h1&gt;\n\n&lt;h1&gt;require-stack-version: &amp;quot;&amp;gt;=2.1&amp;quot;&lt;/h1&gt;\n\n&lt;h1&gt;Override the architecture used by stack, especially useful on Windows&lt;/h1&gt;\n\n&lt;h1&gt;arch: i386&lt;/h1&gt;\n\n&lt;h1&gt;arch: x86_64&lt;/h1&gt;\n\n&lt;h1&gt;Extra directories used by stack for building&lt;/h1&gt;\n\n&lt;h1&gt;extra-include-dirs: [/path/to/dir]&lt;/h1&gt;\n\n&lt;h1&gt;extra-lib-dirs: [/path/to/dir]&lt;/h1&gt;\n\n&lt;h1&gt;Allow a newer minor version of GHC than the snapshot specifies&lt;/h1&gt;\n\n&lt;h1&gt;compiler-check: newer-minor&lt;/h1&gt;\n\n&lt;p&gt;extra-deps:\n - minisat-solver-0.1@sha256:e2ff11b1ca8c66e43f8bb2e04f21bd1b812efb94ff215d74f998c928e7e92dcd,5210&lt;/p&gt;\n\n&lt;p&gt;```&lt;/p&gt;\n\n&lt;p&gt;The cabal file&lt;/p&gt;\n\n&lt;p&gt;```\ncabal-version: 1.12&lt;/p&gt;\n\n&lt;h2&gt;-- This file has been generated from package.yaml by hpack version 0.31.2.&lt;/h2&gt;\n\n&lt;h2&gt;-- see: &lt;a href=\"https://github.com/sol/hpack\"&gt;https://github.com/sol/hpack&lt;/a&gt;&lt;/h2&gt;\n\n&lt;p&gt;-- hash: 9e4c1b8d2c640f6364c7abf13e184823a0c4b7959a05310c93a9b6ff92efad16&lt;/p&gt;\n\n&lt;p&gt;name:           dtl-model-checking\nversion:        0.1.0.0\ndescription:    Please see the README on GitHub at &lt;a href=\"https://github.com/githubuser/dtl-model-checking#readme\"&gt;https://github.com/githubuser/dtl-model-checking#readme&lt;/a&gt;\nhomepage:       &lt;a href=\"https://github.com/githubuser/dtl-model-checking#readme\"&gt;https://github.com/githubuser/dtl-model-checking#readme&lt;/a&gt;\nbug-reports:    &lt;a href=\"https://github.com/githubuser/dtl-model-checking/issues\"&gt;https://github.com/githubuser/dtl-model-checking/issues&lt;/a&gt;\nauthor:         Author name here\nmaintainer:     &lt;a href=\"mailto:example@example.com\"&gt;example@example.com&lt;/a&gt;\ncopyright:      2020 Author name here\nlicense:        BSD3\nlicense-file:   LICENSE\nbuild-type:     Simple\nextra-source-files:\n    README.md\n    ChangeLog.md&lt;/p&gt;\n\n&lt;p&gt;source-repository head\n  type: git\n  location: &lt;a href=\"https://github.com/githubuser/dtl-model-checking\"&gt;https://github.com/githubuser/dtl-model-checking&lt;/a&gt;&lt;/p&gt;\n\n&lt;p&gt;library\n  exposed-modules:\n      Automaton\n      DTLFormula\n      AutomataTheoreticApproach\n      DTS\n      NBA\n      GNBA\n      Ielementary\n      CommonTypes\n      Utils\n      ExampleInstances\n      BMC\n  other-modules:\n      Paths_dtl_model_checking\n  hs-source-dirs:\n      src\n  build-depends:\n      base &amp;gt;=4.7 &amp;amp;&amp;amp; &amp;lt;5\n    , containers\n    , random\n    , minisat-solver &amp;gt;= 0.1\n  default-language: Haskell2010&lt;/p&gt;\n\n&lt;p&gt;executable dtl-model-checking-exe\n  main-is: Main.hs\n  other-modules:\n      Paths_dtl_model_checking\n  hs-source-dirs:\n      app\n  ghc-options: -O -threaded -rtsopts -with-rtsopts=-N\n  build-depends:\n      base &amp;gt;=4.7 &amp;amp;&amp;amp; &amp;lt;5\n    , dtl-model-checking\n    , containers\n    , random\n  default-language: Haskell2010&lt;/p&gt;\n\n&lt;p&gt;test-suite dtl-model-checking-test\n  type: exitcode-stdio-1.0\n  main-is: Spec.hs\n  other-modules:\n      Paths_dtl_model_checking\n  hs-source-dirs:\n      test\n  ghc-options: -O -threaded -rtsopts -with-rtsopts=-N\n  build-depends:\n      base &amp;gt;=4.7 &amp;amp;&amp;amp; &amp;lt;5\n    , dtl-model-checking\n    , containers\n    , hspec\n    , random\n  default-language: Haskell2010&lt;/p&gt;\n\n&lt;p&gt;benchmark dtl-model-checking-benchmark\n  type: exitcode-stdio-1.0 \n  main-is: Bench.hs\n  other-modules:\n      Paths_dtl_model_checking\n  hs-source-dirs:\n      benchmark\n  ghc-options: -O -threaded -fforce-recomp -rtsopts -with-rtsopts=-N\n  build-depends: base &amp;gt;=4.7 &amp;amp;&amp;amp; &amp;lt;5, dtl-model-checking, containers, criterion, random\n  default-language: Haskell2010\n```&lt;/p&gt;\n&lt;/div&gt;&lt;!-- SC_ON --&gt;", "likes": null, "suggested_sort": null, "banned_at_utc": null, "view_count": null, "archived": false, "no_follow": true, "is_crosspostable": false, "pinned": false, "over_18": false, "all_awardings": [], "awarders": [], "media_only": false, "can_gild": false, "spoiler": false, "locked": false, "author_flair_text": null, "treatment_tags": [], "visited": false, "removed_by": null, "num_reports": null, "distinguished": null, "subreddit_id": "t5_2qh36", "mod_reason_by": null, "removal_reason": null, "link_flair_background_color": "", "id": "gmoik7", "is_robot_indexable": true, "report_reasons": null, "author": "augustoperes", "discussion_type": null, "num_comments": 2, "send_replies": true, "whitelist_status": "all_ads", "contest_mode": false, "mod_reports": [], "author_patreon_flair": false, "author_flair_text_color": null, "permalink": "/r/haskell/comments/gmoik7/errorwarning_on_stack_build/", "parent_whitelist_status": "all_ads", "stickied": false, "url": "https://old.reddit.com/r/haskell/comments/gmoik7/errorwarning_on_stack_build/", "subreddit_subscribers": 55194, "created_utc": 1589894754.0, "num_crossposts": 0, "media": null, "is_video": false}}, {"kind": "t3", "data": {"approved_at_utc": null, "subreddit": "haskell", "selftext": "Do you have any examples of libraries in other languages or language features, which really should have implemented a well-known concept (Monoid, Monad, Alternative, whatever), but they fell short because they (probably) didn't know the concept? For example a broken law, a missing function, over-complicated function types, etc.\n\nI encountered multiple such examples, and they always grind my gears. But for the life of me, I can't remember any of them now.", "author_fullname": "t2_b7rje", "saved": false, "mod_reason_title": null, "gilded": 0, "clicked": false, "title": "Examples of Incorrect Abstractions in Other Languages", "link_flair_richtext": [], "subreddit_name_prefixed": "r/haskell", "hidden": false, "pwls": 6, "link_flair_css_class": null, "downs": 0, "hide_score": false, "name": "t3_glz389", "quarantine": false, "link_flair_text_color": "dark", "upvote_ratio": 0.97, "author_flair_background_color": null, "subreddit_type": "public", "ups": 102, "total_awards_received": 0, "media_embed": {}, "author_flair_template_id": null, "is_original_content": false, "user_reports": [], "secure_media": null, "is_reddit_media_domain": false, "is_meta": false, "category": null, "secure_media_embed": {}, "link_flair_text": null, "can_mod_post": false, "score": 102, "approved_by": null, "author_premium": false, "thumbnail": "", "edited": false, "author_flair_css_class": null, "author_flair_richtext": [], "gildings": {}, "content_categories": null, "is_self": true, "mod_note": null, "created": 1589827048.0, "link_flair_type": "text", "wls": 6, "removed_by_category": null, "banned_by": null, "author_flair_type": "text", "domain": "self.haskell", "allow_live_comments": false, "selftext_html": "&lt;!-- SC_OFF --&gt;&lt;div class=\"md\"&gt;&lt;p&gt;Do you have any examples of libraries in other languages or language features, which really should have implemented a well-known concept (Monoid, Monad, Alternative, whatever), but they fell short because they (probably) didn&amp;#39;t know the concept? For example a broken law, a missing function, over-complicated function types, etc.&lt;/p&gt;\n\n&lt;p&gt;I encountered multiple such examples, and they always grind my gears. But for the life of me, I can&amp;#39;t remember any of them now.&lt;/p&gt;\n&lt;/div&gt;&lt;!-- SC_ON --&gt;", "likes": null, "suggested_sort": null, "banned_at_utc": null, "view_count": null, "archived": false, "no_follow": false, "is_crosspostable": false, "pinned": false, "over_18": false, "all_awardings": [], "awarders": [], "media_only": false, "can_gild": false, "spoiler": false, "locked": false, "author_flair_text": null, "treatment_tags": [], "visited": false, "removed_by": null, "num_reports": null, "distinguished": null, "subreddit_id": "t5_2qh36", "mod_reason_by": null, "removal_reason": null, "link_flair_background_color": "", "id": "glz389", "is_robot_indexable": true, "report_reasons": null, "author": "pavelpotocek", "discussion_type": null, "num_comments": 175, "send_replies": true, "whitelist_status": "all_ads", "contest_mode": false, "mod_reports": [], "author_patreon_flair": false, "author_flair_text_color": null, "permalink": "/r/haskell/comments/glz389/examples_of_incorrect_abstractions_in_other/", "parent_whitelist_status": "all_ads", "stickied": false, "url": "https://old.reddit.com/r/haskell/comments/glz389/examples_of_incorrect_abstractions_in_other/", "subreddit_subscribers": 55194, "created_utc": 1589798248.0, "num_crossposts": 0, "media": null, "is_video": false}}, {"kind": "t3", "data": {"approved_at_utc": null, "subreddit": "haskell", "selftext": "", "author_fullname": "t2_2o6ongui", "saved": false, "mod_reason_title": null, "gilded": 0, "clicked": false, "title": "[ANN] Medea - a json schema language", "link_flair_richtext": [], "subreddit_name_prefixed": "r/haskell", "hidden": false, "pwls": 6, "link_flair_css_class": null, "downs": 0, "hide_score": false, "name": "t3_gma3p4", "quarantine": false, "link_flair_text_color": "dark", "upvote_ratio": 1.0, "author_flair_background_color": null, "subreddit_type": "public", "ups": 14, "total_awards_received": 0, "media_embed": {}, "author_flair_template_id": null, "is_original_content": false, "user_reports": [], "secure_media": null, "is_reddit_media_domain": false, "is_meta": false, "category": null, "secure_media_embed": {}, "link_flair_text": null, "can_mod_post": false, "score": 14, "approved_by": null, "author_premium": false, "thumbnail": "", "edited": false, "author_flair_css_class": null, "author_flair_richtext": [], "gildings": {}, "content_categories": null, "is_self": false, "mod_note": null, "created": 1589864384.0, "link_flair_type": "text", "wls": 6, "removed_by_category": null, "banned_by": null, "author_flair_type": "text", "domain": "github.com", "allow_live_comments": false, "selftext_html": null, "likes": null, "suggested_sort": null, "banned_at_utc": null, "view_count": null, "archived": false, "no_follow": false, "is_crosspostable": false, "pinned": false, "over_18": false, "all_awardings": [], "awarders": [], "media_only": false, "can_gild": false, "spoiler": false, "locked": false, "author_flair_text": null, "treatment_tags": [], "visited": false, "removed_by": null, "num_reports": null, "distinguished": null, "subreddit_id": "t5_2qh36", "mod_reason_by": null, "removal_reason": null, "link_flair_background_color": "", "id": "gma3p4", "is_robot_indexable": true, "report_reasons": null, "author": "restarted_mustard", "discussion_type": null, "num_comments": 2, "send_replies": true, "whitelist_status": "all_ads", "contest_mode": false, "mod_reports": [], "author_patreon_flair": false, "author_flair_text_color": null, "permalink": "/r/haskell/comments/gma3p4/ann_medea_a_json_schema_language/", "parent_whitelist_status": "all_ads", "stickied": false, "url": "https://github.com/juspay/medea", "subreddit_subscribers": 55194, "created_utc": 1589835584.0, "num_crossposts": 0, "media": null, "is_video": false}}, {"kind": "t3", "data": {"approved_at_utc": null, "subreddit": "haskell", "selftext": "There seem to be some [posts](https://www.reddit.com/r/haskell/comments/pen8s/anyone_else_used_write_yourself_a_scheme_in_48/) about the book or the [Write You a Scheme V2.0](https://wespiser.com/writings/wyas/00_overview.html), but I'm unsure how much Scheme I need to tackle this project.\n\nI've thumbed through the (in)famous Learn You a Haskell, and implementing an interpreter sounds like a lot of fun, but perhaps I might not down this path if I have to spend the time to buckle down and learn some Scheme syntax too.", "author_fullname": "t2_5y26z8w2", "saved": false, "mod_reason_title": null, "gilded": 0, "clicked": false, "title": "How much Scheme needed for \"Write yourself a Scheme in 48 hours?\"", "link_flair_richtext": [], "subreddit_name_prefixed": "r/haskell", "hidden": false, "pwls": 6, "link_flair_css_class": null, "downs": 0, "hide_score": false, "name": "t3_gm3ia1", "quarantine": false, "link_flair_text_color": "dark", "upvote_ratio": 0.97, "author_flair_background_color": null, "subreddit_type": "public", "ups": 22, "total_awards_received": 0, "media_embed": {}, "author_flair_template_id": null, "is_original_content": false, "user_reports": [], "secure_media": null, "is_reddit_media_domain": false, "is_meta": false, "category": null, "secure_media_embed": {}, "link_flair_text": null, "can_mod_post": false, "score": 22, "approved_by": null, "author_premium": false, "thumbnail": "", "edited": false, "author_flair_css_class": null, "author_flair_richtext": [], "gildings": {}, "content_categories": null, "is_self": true, "mod_note": null, "created": 1589844357.0, "link_flair_type": "text", "wls": 6, "removed_by_category": null, "banned_by": null, "author_flair_type": "text", "domain": "self.haskell", "allow_live_comments": false, "selftext_html": "&lt;!-- SC_OFF --&gt;&lt;div class=\"md\"&gt;&lt;p&gt;There seem to be some &lt;a href=\"https://www.reddit.com/r/haskell/comments/pen8s/anyone_else_used_write_yourself_a_scheme_in_48/\"&gt;posts&lt;/a&gt; about the book or the &lt;a href=\"https://wespiser.com/writings/wyas/00_overview.html\"&gt;Write You a Scheme V2.0&lt;/a&gt;, but I&amp;#39;m unsure how much Scheme I need to tackle this project.&lt;/p&gt;\n\n&lt;p&gt;I&amp;#39;ve thumbed through the (in)famous Learn You a Haskell, and implementing an interpreter sounds like a lot of fun, but perhaps I might not down this path if I have to spend the time to buckle down and learn some Scheme syntax too.&lt;/p&gt;\n&lt;/div&gt;&lt;!-- SC_ON --&gt;", "likes": null, "suggested_sort": null, "banned_at_utc": null, "view_count": null, "archived": false, "no_follow": false, "is_crosspostable": false, "pinned": false, "over_18": false, "all_awardings": [], "awarders": [], "media_only": false, "can_gild": false, "spoiler": false, "locked": false, "author_flair_text": null, "treatment_tags": [], "visited": false, "removed_by": null, "num_reports": null, "distinguished": null, "subreddit_id": "t5_2qh36", "mod_reason_by": null, "removal_reason": null, "link_flair_background_color": "", "id": "gm3ia1", "is_robot_indexable": true, "report_reasons": null, "author": "0x2fwhc", "discussion_type": null, "num_comments": 5, "send_replies": false, "whitelist_status": "all_ads", "contest_mode": false, "mod_reports": [], "author_patreon_flair": false, "author_flair_text_color": null, "permalink": "/r/haskell/comments/gm3ia1/how_much_scheme_needed_for_write_yourself_a/", "parent_whitelist_status": "all_ads", "stickied": false, "url": "https://old.reddit.com/r/haskell/comments/gm3ia1/how_much_scheme_needed_for_write_yourself_a/", "subreddit_subscribers": 55194, "created_utc": 1589815557.0, "num_crossposts": 0, "media": null, "is_video": false}}, {"kind": "t3", "data": {"approved_at_utc": null, "subreddit": "haskell", "selftext": "GHC has releases versions 8.4.x, and 8.6.x, but there are no 8.5.x releases. Why does GHC skip odd minor versions?", "author_fullname": "t2_2lv4dufx", "saved": false, "mod_reason_title": null, "gilded": 0, "clicked": false, "title": "GHC versioning scheme", "link_flair_richtext": [], "subreddit_name_prefixed": "r/haskell", "hidden": false, "pwls": 6, "link_flair_css_class": null, "downs": 0, "hide_score": false, "name": "t3_gm6mm7", "quarantine": false, "link_flair_text_color": "dark", "upvote_ratio": 0.91, "author_flair_background_color": null, "subreddit_type": "public", "ups": 8, "total_awards_received": 0, "media_embed": {}, "author_flair_template_id": null, "is_original_content": false, "user_reports": [], "secure_media": null, "is_reddit_media_domain": false, "is_meta": false, "category": null, "secure_media_embed": {}, "link_flair_text": null, "can_mod_post": false, "score": 8, "approved_by": null, "author_premium": false, "thumbnail": "", "edited": false, "author_flair_css_class": null, "author_flair_richtext": [], "gildings": {}, "content_categories": null, "is_self": true, "mod_note": null, "created": 1589853843.0, "link_flair_type": "text", "wls": 6, "removed_by_category": null, "banned_by": null, "author_flair_type": "text", "domain": "self.haskell", "allow_live_comments": false, "selftext_html": "&lt;!-- SC_OFF --&gt;&lt;div class=\"md\"&gt;&lt;p&gt;GHC has releases versions 8.4.x, and 8.6.x, but there are no 8.5.x releases. Why does GHC skip odd minor versions?&lt;/p&gt;\n&lt;/div&gt;&lt;!-- SC_ON --&gt;", "likes": null, "suggested_sort": null, "banned_at_utc": null, "view_count": null, "archived": false, "no_follow": false, "is_crosspostable": false, "pinned": false, "over_18": false, "all_awardings": [], "awarders": [], "media_only": false, "can_gild": false, "spoiler": false, "locked": false, "author_flair_text": null, "treatment_tags": [], "visited": false, "removed_by": null, "num_reports": null, "distinguished": null, "subreddit_id": "t5_2qh36", "mod_reason_by": null, "removal_reason": null, "link_flair_background_color": "", "id": "gm6mm7", "is_robot_indexable": true, "report_reasons": null, "author": "NinjaPenguin54", "discussion_type": null, "num_comments": 6, "send_replies": true, "whitelist_status": "all_ads", "contest_mode": false, "mod_reports": [], "author_patreon_flair": false, "author_flair_text_color": null, "permalink": "/r/haskell/comments/gm6mm7/ghc_versioning_scheme/", "parent_whitelist_status": "all_ads", "stickied": false, "url": "https://old.reddit.com/r/haskell/comments/gm6mm7/ghc_versioning_scheme/", "subreddit_subscribers": 55194, "created_utc": 1589825043.0, "num_crossposts": 0, "media": null, "is_video": false}}, {"kind": "t3", "data": {"approved_at_utc": null, "subreddit": "haskell", "selftext": "Hello fellow Haskellers,\n\nI've spent last half year learning Haskell and managed to write my first real-world Haskell application. Now I have some ideas for Haskell libraries, that could be (hopefully) useful, but have zero experience designing library for Haskell (mainly from API perspective). Building library is clearly different than building CLI tool, as the main \"API\" of CLI tool is the command line interface, which is pretty restrictive, but library API should be more flexible to suit different styles and designs of end-user programs. Also if such library is badly designed from start, it's hard to completely change the API style as it breaks compatibility and causes troubles. So I'd like to ask you to share your experience on this topic, mainly following points:\n\n1. **handling exceptions** \\- I know, this is probably controversial topic, but I'd like to know whether there is any current consensus. Let's say that my library will provide IO operations that may fail because 1/ there is no result for the given input or 2/ there is some IO error (file doesn't exist, etc.). In my CLI tool, I used the approach summarized by u/snoyberg in [this blog post](https://www.fpcomplete.com/blog/2016/11/exceptions-best-practices-haskell), i.e. using `MonadThrow` with `MonadIO`, like `parseJsonFile :: (MonadThrow m, MonadIO m) =&gt; FilePath -&gt; m JSON`. But I'm wondering if this is good approach for library? Because the `MonadThrow` itself isn't really specific about the type of the error it can throw. Would it be better to use something as `MonadError` maybe?\n2. **RIO** \\- In my CLI app I'm pretty happy with [RIO](https://hackage.haskell.org/package/rio), both as Prelude replacement and RIO Monad, but I guess it's not good idea to force end-users to use the RIO-style in library, right?\n3. **language extensions** \\- GHC language extensions are pretty common to use nowadays, but are there any of them I should explicitly avoid using in libraries?\n4. **overall architecture** \\- This is closely related to 1). Should I go full mtl for the library design, or maybe keep it simpler and use just some combination of things like `MonadIO`, `MonadThrow` or `MonadError`?\n\nI'll be grateful for any shared experience, comments, links to blog posts/book. Thanks a lot in advance.", "author_fullname": "t2_kjucw", "saved": false, "mod_reason_title": null, "gilded": 0, "clicked": false, "title": "Designing Haskell library - best practices?", "link_flair_richtext": [], "subreddit_name_prefixed": "r/haskell", "hidden": false, "pwls": 6, "link_flair_css_class": null, "downs": 0, "hide_score": false, "name": "t3_gm3v3g", "quarantine": false, "link_flair_text_color": "dark", "upvote_ratio": 0.92, "author_flair_background_color": null, "subreddit_type": "public", "ups": 10, "total_awards_received": 0, "media_embed": {}, "author_flair_template_id": null, "is_original_content": false, "user_reports": [], "secure_media": null, "is_reddit_media_domain": false, "is_meta": false, "category": null, "secure_media_embed": {}, "link_flair_text": null, "can_mod_post": false, "score": 10, "approved_by": null, "author_premium": false, "thumbnail": "", "edited": false, "author_flair_css_class": null, "author_flair_richtext": [], "gildings": {}, "content_categories": null, "is_self": true, "mod_note": null, "created": 1589845467.0, "link_flair_type": "text", "wls": 6, "removed_by_category": null, "banned_by": null, "author_flair_type": "text", "domain": "self.haskell", "allow_live_comments": false, "selftext_html": "&lt;!-- SC_OFF --&gt;&lt;div class=\"md\"&gt;&lt;p&gt;Hello fellow Haskellers,&lt;/p&gt;\n\n&lt;p&gt;I&amp;#39;ve spent last half year learning Haskell and managed to write my first real-world Haskell application. Now I have some ideas for Haskell libraries, that could be (hopefully) useful, but have zero experience designing library for Haskell (mainly from API perspective). Building library is clearly different than building CLI tool, as the main &amp;quot;API&amp;quot; of CLI tool is the command line interface, which is pretty restrictive, but library API should be more flexible to suit different styles and designs of end-user programs. Also if such library is badly designed from start, it&amp;#39;s hard to completely change the API style as it breaks compatibility and causes troubles. So I&amp;#39;d like to ask you to share your experience on this topic, mainly following points:&lt;/p&gt;\n\n&lt;ol&gt;\n&lt;li&gt;&lt;strong&gt;handling exceptions&lt;/strong&gt; - I know, this is probably controversial topic, but I&amp;#39;d like to know whether there is any current consensus. Let&amp;#39;s say that my library will provide IO operations that may fail because 1/ there is no result for the given input or 2/ there is some IO error (file doesn&amp;#39;t exist, etc.). In my CLI tool, I used the approach summarized by &lt;a href=\"/u/snoyberg\"&gt;u/snoyberg&lt;/a&gt; in &lt;a href=\"https://www.fpcomplete.com/blog/2016/11/exceptions-best-practices-haskell\"&gt;this blog post&lt;/a&gt;, i.e. using &lt;code&gt;MonadThrow&lt;/code&gt; with &lt;code&gt;MonadIO&lt;/code&gt;, like &lt;code&gt;parseJsonFile :: (MonadThrow m, MonadIO m) =&amp;gt; FilePath -&amp;gt; m JSON&lt;/code&gt;. But I&amp;#39;m wondering if this is good approach for library? Because the &lt;code&gt;MonadThrow&lt;/code&gt; itself isn&amp;#39;t really specific about the type of the error it can throw. Would it be better to use something as &lt;code&gt;MonadError&lt;/code&gt; maybe?&lt;/li&gt;\n&lt;li&gt;&lt;strong&gt;RIO&lt;/strong&gt; - In my CLI app I&amp;#39;m pretty happy with &lt;a href=\"https://hackage.haskell.org/package/rio\"&gt;RIO&lt;/a&gt;, both as Prelude replacement and RIO Monad, but I guess it&amp;#39;s not good idea to force end-users to use the RIO-style in library, right?&lt;/li&gt;\n&lt;li&gt;&lt;strong&gt;language extensions&lt;/strong&gt; - GHC language extensions are pretty common to use nowadays, but are there any of them I should explicitly avoid using in libraries?&lt;/li&gt;\n&lt;li&gt;&lt;strong&gt;overall architecture&lt;/strong&gt; - This is closely related to 1). Should I go full mtl for the library design, or maybe keep it simpler and use just some combination of things like &lt;code&gt;MonadIO&lt;/code&gt;, &lt;code&gt;MonadThrow&lt;/code&gt; or &lt;code&gt;MonadError&lt;/code&gt;?&lt;/li&gt;\n&lt;/ol&gt;\n\n&lt;p&gt;I&amp;#39;ll be grateful for any shared experience, comments, links to blog posts/book. Thanks a lot in advance.&lt;/p&gt;\n&lt;/div&gt;&lt;!-- SC_ON --&gt;", "likes": null, "suggested_sort": null, "banned_at_utc": null, "view_count": null, "archived": false, "no_follow": false, "is_crosspostable": false, "pinned": false, "over_18": false, "all_awardings": [], "awarders": [], "media_only": false, "can_gild": false, "spoiler": false, "locked": false, "author_flair_text": null, "treatment_tags": [], "visited": false, "removed_by": null, "num_reports": null, "distinguished": null, "subreddit_id": "t5_2qh36", "mod_reason_by": null, "removal_reason": null, "link_flair_background_color": "", "id": "gm3v3g", "is_robot_indexable": true, "report_reasons": null, "author": "xwinus", "discussion_type": null, "num_comments": 5, "send_replies": true, "whitelist_status": "all_ads", "contest_mode": false, "mod_reports": [], "author_patreon_flair": false, "author_flair_text_color": null, "permalink": "/r/haskell/comments/gm3v3g/designing_haskell_library_best_practices/", "parent_whitelist_status": "all_ads", "stickied": false, "url": "https://old.reddit.com/r/haskell/comments/gm3v3g/designing_haskell_library_best_practices/", "subreddit_subscribers": 55194, "created_utc": 1589816667.0, "num_crossposts": 0, "media": null, "is_video": false}}, {"kind": "t3", "data": {"approved_at_utc": null, "subreddit": "haskell", "selftext": "Un dictionnaire en Python peut contenir des donn\u00e9es de toute sortes de type.\n\nDans ce nouveau chapitre, nous allons utiliser le syst\u00e8me de type pour cr\u00e9er des enregistrements \u00ab extensibles \u00bb, ce qui revient \u00e0 appliquer des r\u00e8gles de typage aux objets ad hoc des langages dynamiques.\n\nC'est un bon pr\u00e9texte pour faire un retour sur plusieurs notions d\u00e9j\u00e0 abord\u00e9es : les repr\u00e9sentations canoniques, les Types Somme, Produit, existentiels, de rang n et les types de donn\u00e9e alg\u00e9briques g\u00e9n\u00e9ralis\u00e9s.\n\nEn s'exer\u00e7ant \u00e0 leur usage, nous verrons aussi de nouvelles notions et pratiques, comme :\n\n* les types index\u00e9s,\n* les tandems de constructeurs de donn\u00e9e dangereux rendus s\u00fbr par des constructeurs intelligents,\n* des \u00e9l\u00e9ments du module GHC.TypeLits et du paquet first-class-families,\n* se servir de familles de types comme contrainte ou index sur un type Produit,\n* les \u00e9tiquettes surcharg\u00e9es (extension OverloadedLabels) qui permettent de transformer `get (Key @\"example\") foo` en `get #example foo` (c'est aussi l'occasion de parler d'astuce de contrainte et d'en-t\u00eate d\u2019instance).\n\nFa\u00eetes circuler l'info s'il vous pla\u00eet, \u00e7a me rend bien service.\n\nBonne r\u00e9flexion !", "author_fullname": "t2_167bmq", "saved": false, "mod_reason_title": null, "gilded": 0, "clicked": false, "title": "\"Penser en Types\" - Chapitre 11 (update in the translation of \"Thinking with Types\")", "link_flair_richtext": [], "subreddit_name_prefixed": "r/haskell", "hidden": false, "pwls": 6, "link_flair_css_class": null, "downs": 0, "hide_score": false, "name": "t3_gm5nzd", "quarantine": false, "link_flair_text_color": "dark", "upvote_ratio": 0.69, "author_flair_background_color": null, "subreddit_type": "public", "ups": 5, "total_awards_received": 0, "media_embed": {}, "author_flair_template_id": null, "is_original_content": false, "user_reports": [], "secure_media": null, "is_reddit_media_domain": false, "is_meta": false, "category": null, "secure_media_embed": {}, "link_flair_text": null, "can_mod_post": false, "score": 5, "approved_by": null, "author_premium": false, "thumbnail": "", "edited": false, "author_flair_css_class": null, "author_flair_richtext": [], "gildings": {}, "content_categories": null, "is_self": true, "mod_note": null, "created": 1589850981.0, "link_flair_type": "text", "wls": 6, "removed_by_category": null, "banned_by": null, "author_flair_type": "text", "domain": "self.haskell", "allow_live_comments": false, "selftext_html": "&lt;!-- SC_OFF --&gt;&lt;div class=\"md\"&gt;&lt;p&gt;Un dictionnaire en Python peut contenir des donn\u00e9es de toute sortes de type.&lt;/p&gt;\n\n&lt;p&gt;Dans ce nouveau chapitre, nous allons utiliser le syst\u00e8me de type pour cr\u00e9er des enregistrements \u00ab extensibles \u00bb, ce qui revient \u00e0 appliquer des r\u00e8gles de typage aux objets ad hoc des langages dynamiques.&lt;/p&gt;\n\n&lt;p&gt;C&amp;#39;est un bon pr\u00e9texte pour faire un retour sur plusieurs notions d\u00e9j\u00e0 abord\u00e9es : les repr\u00e9sentations canoniques, les Types Somme, Produit, existentiels, de rang n et les types de donn\u00e9e alg\u00e9briques g\u00e9n\u00e9ralis\u00e9s.&lt;/p&gt;\n\n&lt;p&gt;En s&amp;#39;exer\u00e7ant \u00e0 leur usage, nous verrons aussi de nouvelles notions et pratiques, comme :&lt;/p&gt;\n\n&lt;ul&gt;\n&lt;li&gt;les types index\u00e9s,&lt;/li&gt;\n&lt;li&gt;les tandems de constructeurs de donn\u00e9e dangereux rendus s\u00fbr par des constructeurs intelligents,&lt;/li&gt;\n&lt;li&gt;des \u00e9l\u00e9ments du module GHC.TypeLits et du paquet first-class-families,&lt;/li&gt;\n&lt;li&gt;se servir de familles de types comme contrainte ou index sur un type Produit,&lt;/li&gt;\n&lt;li&gt;les \u00e9tiquettes surcharg\u00e9es (extension OverloadedLabels) qui permettent de transformer &lt;code&gt;get (Key @&amp;quot;example&amp;quot;) foo&lt;/code&gt; en &lt;code&gt;get #example foo&lt;/code&gt; (c&amp;#39;est aussi l&amp;#39;occasion de parler d&amp;#39;astuce de contrainte et d&amp;#39;en-t\u00eate d\u2019instance).&lt;/li&gt;\n&lt;/ul&gt;\n\n&lt;p&gt;Fa\u00eetes circuler l&amp;#39;info s&amp;#39;il vous pla\u00eet, \u00e7a me rend bien service.&lt;/p&gt;\n\n&lt;p&gt;Bonne r\u00e9flexion !&lt;/p&gt;\n&lt;/div&gt;&lt;!-- SC_ON --&gt;", "likes": null, "suggested_sort": null, "banned_at_utc": null, "view_count": null, "archived": false, "no_follow": false, "is_crosspostable": false, "pinned": false, "over_18": false, "all_awardings": [], "awarders": [], "media_only": false, "can_gild": false, "spoiler": false, "locked": false, "author_flair_text": null, "treatment_tags": [], "visited": false, "removed_by": null, "num_reports": null, "distinguished": null, "subreddit_id": "t5_2qh36", "mod_reason_by": null, "removal_reason": null, "link_flair_background_color": "", "id": "gm5nzd", "is_robot_indexable": true, "report_reasons": null, "author": "jhderaigniac", "discussion_type": null, "num_comments": 0, "send_replies": true, "whitelist_status": "all_ads", "contest_mode": false, "mod_reports": [], "author_patreon_flair": false, "author_flair_text_color": null, "permalink": "/r/haskell/comments/gm5nzd/penser_en_types_chapitre_11_update_in_the/", "parent_whitelist_status": "all_ads", "stickied": false, "url": "https://old.reddit.com/r/haskell/comments/gm5nzd/penser_en_types_chapitre_11_update_in_the/", "subreddit_subscribers": 55194, "created_utc": 1589822181.0, "num_crossposts": 0, "media": null, "is_video": false}}, {"kind": "t3", "data": {"approved_at_utc": null, "subreddit": "haskell", "selftext": "Hello,\n\nI could not find the answer anywhere so I thought I might ask here. My package was included in Stackage sometime at the end of April, but it's still not in any LTS release even though there have been a couple of LTS version bumps since then. What is the policy here? Is there anything I should do? Thanks in advance", "author_fullname": "t2_3epm", "saved": false, "mod_reason_title": null, "gilded": 0, "clicked": false, "title": "When packages are promoted to LTS in Stackage?", "link_flair_richtext": [], "subreddit_name_prefixed": "r/haskell", "hidden": false, "pwls": 6, "link_flair_css_class": null, "downs": 0, "hide_score": false, "name": "t3_gm2484", "quarantine": false, "link_flair_text_color": "dark", "upvote_ratio": 1.0, "author_flair_background_color": null, "subreddit_type": "public", "ups": 6, "total_awards_received": 0, "media_embed": {}, "author_flair_template_id": null, "is_original_content": false, "user_reports": [], "secure_media": null, "is_reddit_media_domain": false, "is_meta": false, "category": null, "secure_media_embed": {}, "link_flair_text": null, "can_mod_post": false, "score": 6, "approved_by": null, "author_premium": false, "thumbnail": "", "edited": false, "author_flair_css_class": null, "author_flair_richtext": [], "gildings": {}, "content_categories": null, "is_self": true, "mod_note": null, "created": 1589839723.0, "link_flair_type": "text", "wls": 6, "removed_by_category": null, "banned_by": null, "author_flair_type": "text", "domain": "self.haskell", "allow_live_comments": false, "selftext_html": "&lt;!-- SC_OFF --&gt;&lt;div class=\"md\"&gt;&lt;p&gt;Hello,&lt;/p&gt;\n\n&lt;p&gt;I could not find the answer anywhere so I thought I might ask here. My package was included in Stackage sometime at the end of April, but it&amp;#39;s still not in any LTS release even though there have been a couple of LTS version bumps since then. What is the policy here? Is there anything I should do? Thanks in advance&lt;/p&gt;\n&lt;/div&gt;&lt;!-- SC_ON --&gt;", "likes": null, "suggested_sort": null, "banned_at_utc": null, "view_count": null, "archived": false, "no_follow": false, "is_crosspostable": false, "pinned": false, "over_18": false, "all_awardings": [], "awarders": [], "media_only": false, "can_gild": false, "spoiler": false, "locked": false, "author_flair_text": null, "treatment_tags": [], "visited": false, "removed_by": null, "num_reports": null, "distinguished": null, "subreddit_id": "t5_2qh36", "mod_reason_by": null, "removal_reason": null, "link_flair_background_color": "", "id": "gm2484", "is_robot_indexable": true, "report_reasons": null, "author": "rzeznik", "discussion_type": null, "num_comments": 2, "send_replies": true, "whitelist_status": "all_ads", "contest_mode": false, "mod_reports": [], "author_patreon_flair": false, "author_flair_text_color": null, "permalink": "/r/haskell/comments/gm2484/when_packages_are_promoted_to_lts_in_stackage/", "parent_whitelist_status": "all_ads", "stickied": false, "url": "https://old.reddit.com/r/haskell/comments/gm2484/when_packages_are_promoted_to_lts_in_stackage/", "subreddit_subscribers": 55194, "created_utc": 1589810923.0, "num_crossposts": 0, "media": null, "is_video": false}}, {"kind": "t3", "data": {"approved_at_utc": null, "subreddit": "haskell", "selftext": "", "author_fullname": "t2_o5q8o", "saved": false, "mod_reason_title": null, "gilded": 0, "clicked": false, "title": "[ANN] password-2.0: library for working with passwords and password hashes", "link_flair_richtext": [], "subreddit_name_prefixed": "r/haskell", "hidden": false, "pwls": 6, "link_flair_css_class": null, "downs": 0, "hide_score": false, "name": "t3_glte2r", "quarantine": false, "link_flair_text_color": "dark", "upvote_ratio": 0.95, "author_flair_background_color": null, "subreddit_type": "public", "ups": 45, "total_awards_received": 0, "media_embed": {}, "author_flair_template_id": null, "is_original_content": false, "user_reports": [], "secure_media": null, "is_reddit_media_domain": false, "is_meta": false, "category": null, "secure_media_embed": {}, "link_flair_text": null, "can_mod_post": false, "score": 45, "approved_by": null, "author_premium": false, "thumbnail": "", "edited": false, "author_flair_css_class": null, "author_flair_richtext": [], "gildings": {}, "content_categories": null, "is_self": false, "mod_note": null, "created": 1589800022.0, "link_flair_type": "text", "wls": 6, "removed_by_category": null, "banned_by": null, "author_flair_type": "text", "domain": "functor.tokyo", "allow_live_comments": false, "selftext_html": null, "likes": null, "suggested_sort": null, "banned_at_utc": null, "view_count": null, "archived": false, "no_follow": false, "is_crosspostable": false, "pinned": false, "over_18": false, "all_awardings": [], "awarders": [], "media_only": false, "can_gild": false, "spoiler": false, "locked": false, "author_flair_text": null, "treatment_tags": [], "visited": false, "removed_by": null, "num_reports": null, "distinguished": null, "subreddit_id": "t5_2qh36", "mod_reason_by": null, "removal_reason": null, "link_flair_background_color": "", "id": "glte2r", "is_robot_indexable": true, "report_reasons": null, "author": "cdep_illabout", "discussion_type": null, "num_comments": 0, "send_replies": true, "whitelist_status": "all_ads", "contest_mode": false, "mod_reports": [], "author_patreon_flair": false, "author_flair_text_color": null, "permalink": "/r/haskell/comments/glte2r/ann_password20_library_for_working_with_passwords/", "parent_whitelist_status": "all_ads", "stickied": false, "url": "https://functor.tokyo/blog/2020-05-18-password-2.0", "subreddit_subscribers": 55194, "created_utc": 1589771222.0, "num_crossposts": 0, "media": null, "is_video": false}}, {"kind": "t3", "data": {"approved_at_utc": null, "subreddit": "haskell", "selftext": "", "author_fullname": "t2_137hg4", "saved": false, "mod_reason_title": null, "gilded": 0, "clicked": false, "title": "Trade-Offs in Type Safety", "link_flair_richtext": [], "subreddit_name_prefixed": "r/haskell", "hidden": false, "pwls": 6, "link_flair_css_class": null, "downs": 0, "hide_score": false, "name": "t3_glzz0l", "quarantine": false, "link_flair_text_color": "dark", "upvote_ratio": 0.68, "author_flair_background_color": null, "subreddit_type": "public", "ups": 7, "total_awards_received": 0, "media_embed": {}, "author_flair_template_id": null, "is_original_content": false, "user_reports": [], "secure_media": null, "is_reddit_media_domain": false, "is_meta": false, "category": null, "secure_media_embed": {}, "link_flair_text": null, "can_mod_post": false, "score": 7, "approved_by": null, "author_premium": false, "thumbnail": "", "edited": false, "author_flair_css_class": null, "author_flair_richtext": [], "gildings": {}, "content_categories": null, "is_self": false, "mod_note": null, "created": 1589831325.0, "link_flair_type": "text", "wls": 6, "removed_by_category": null, "banned_by": null, "author_flair_type": "text", "domain": "alpacaaa.net", "allow_live_comments": false, "selftext_html": null, "likes": null, "suggested_sort": null, "banned_at_utc": null, "view_count": null, "archived": false, "no_follow": false, "is_crosspostable": false, "pinned": false, "over_18": false, "all_awardings": [], "awarders": [], "media_only": false, "can_gild": false, "spoiler": false, "locked": false, "author_flair_text": null, "treatment_tags": [], "visited": false, "removed_by": null, "num_reports": null, "distinguished": null, "subreddit_id": "t5_2qh36", "mod_reason_by": null, "removal_reason": null, "link_flair_background_color": "", "id": "glzz0l", "is_robot_indexable": true, "report_reasons": null, "author": "_alpacaaa", "discussion_type": null, "num_comments": 27, "send_replies": true, "whitelist_status": "all_ads", "contest_mode": false, "mod_reports": [], "author_patreon_flair": false, "author_flair_text_color": null, "permalink": "/r/haskell/comments/glzz0l/tradeoffs_in_type_safety/", "parent_whitelist_status": "all_ads", "stickied": false, "url": "https://alpacaaa.net/type-safety/", "subreddit_subscribers": 55194, "created_utc": 1589802525.0, "num_crossposts": 0, "media": null, "is_video": false}}, {"kind": "t3", "data": {"approved_at_utc": null, "subreddit": "haskell", "selftext": "The Chalmers Online Functional Programming Seminar Series is organized by the Chalmers Functional Programming Group, as a way to exploit the fact that so many of us in the FP community are already meeting and working online these days. Our aim is to bring the people in the FP community closer together, to educate and inspire, and to foster collaboration.\n\nThe seminars will take place every Monday (at 7am PDT / 10am EDT / 16:00 CEST) and are **live streamed through YouTube**, and questions are taken through **sli.do**.\n\nWe continue tomorrow with Benjamin Pierce; title \"Backtracking Generators for Random Testing\". All welcome!\n\nLink to program, including videos of previous talks:\n\nhttp://chalmersfp.org/", "author_fullname": "t2_9ork9", "saved": false, "mod_reason_title": null, "gilded": 0, "clicked": false, "title": "Reminder: The Chalmers Online Functional Programming Seminar Series continues tomorrow (Monday) with a talk by Benjamin Pierce", "link_flair_richtext": [], "subreddit_name_prefixed": "r/haskell", "hidden": false, "pwls": 6, "link_flair_css_class": null, "downs": 0, "hide_score": false, "name": "t3_gld45o", "quarantine": false, "link_flair_text_color": "dark", "upvote_ratio": 0.98, "author_flair_background_color": null, "subreddit_type": "public", "ups": 87, "total_awards_received": 0, "media_embed": {}, "author_flair_template_id": null, "is_original_content": false, "user_reports": [], "secure_media": null, "is_reddit_media_domain": false, "is_meta": false, "category": null, "secure_media_embed": {}, "link_flair_text": null, "can_mod_post": false, "score": 87, "approved_by": null, "author_premium": false, "thumbnail": "", "edited": 1589711120.0, "author_flair_css_class": null, "author_flair_richtext": [], "gildings": {}, "content_categories": null, "is_self": true, "mod_note": null, "created": 1589739615.0, "link_flair_type": "text", "wls": 6, "removed_by_category": null, "banned_by": null, "author_flair_type": "text", "domain": "self.haskell", "allow_live_comments": false, "selftext_html": "&lt;!-- SC_OFF --&gt;&lt;div class=\"md\"&gt;&lt;p&gt;The Chalmers Online Functional Programming Seminar Series is organized by the Chalmers Functional Programming Group, as a way to exploit the fact that so many of us in the FP community are already meeting and working online these days. Our aim is to bring the people in the FP community closer together, to educate and inspire, and to foster collaboration.&lt;/p&gt;\n\n&lt;p&gt;The seminars will take place every Monday (at 7am PDT / 10am EDT / 16:00 CEST) and are &lt;strong&gt;live streamed through YouTube&lt;/strong&gt;, and questions are taken through &lt;strong&gt;sli.do&lt;/strong&gt;.&lt;/p&gt;\n\n&lt;p&gt;We continue tomorrow with Benjamin Pierce; title &amp;quot;Backtracking Generators for Random Testing&amp;quot;. All welcome!&lt;/p&gt;\n\n&lt;p&gt;Link to program, including videos of previous talks:&lt;/p&gt;\n\n&lt;p&gt;&lt;a href=\"http://chalmersfp.org/\"&gt;http://chalmersfp.org/&lt;/a&gt;&lt;/p&gt;\n&lt;/div&gt;&lt;!-- SC_ON --&gt;", "likes": null, "suggested_sort": null, "banned_at_utc": null, "view_count": null, "archived": false, "no_follow": false, "is_crosspostable": false, "pinned": false, "over_18": false, "all_awardings": [], "awarders": [], "media_only": false, "can_gild": false, "spoiler": false, "locked": false, "author_flair_text": null, "treatment_tags": [], "visited": false, "removed_by": null, "num_reports": null, "distinguished": null, "subreddit_id": "t5_2qh36", "mod_reason_by": null, "removal_reason": null, "link_flair_background_color": "", "id": "gld45o", "is_robot_indexable": true, "report_reasons": null, "author": "koenclaessen", "discussion_type": null, "num_comments": 4, "send_replies": true, "whitelist_status": "all_ads", "contest_mode": false, "mod_reports": [], "author_patreon_flair": false, "author_flair_text_color": null, "permalink": "/r/haskell/comments/gld45o/reminder_the_chalmers_online_functional/", "parent_whitelist_status": "all_ads", "stickied": false, "url": "https://old.reddit.com/r/haskell/comments/gld45o/reminder_the_chalmers_online_functional/", "subreddit_subscribers": 55194, "created_utc": 1589710815.0, "num_crossposts": 0, "media": null, "is_video": false}}], "after": "t3_gld45o", "before": null}}
Object
  [ ( "kind" , String "Listing" )
  , ( "data"
    , Object
        [ ( "modhash" , String "" )
        , ( "dist" , Number (26 % 1) )
        , ( "children"
          , Array
              [ Object
                  [ ( "kind" , String "t3" )
                  , ( "data"
                    , Object
                        [ ( "approved_at_utc" , Null )
                        , ( "subreddit" , String "haskell" )
                        , ( "selftext"
                          , String
                              "This is your opportunity to ask any questions you feel don't deserve their own threads, no matter how small or simple they might be!"
                          )
                        , ( "author_fullname" , String "t2_6l4z3" )
                        , ( "saved" , Boolean False )
                        , ( "mod_reason_title" , Null )
                        , ( "gilded" , Number (0 % 1) )
                        , ( "clicked" , Boolean False )
                        , ( "title" , String "Monthly Hask Anything (May 2020)" )
                        , ( "link_flair_richtext" , Array [] )
                        , ( "subreddit_name_prefixed" , String "r/haskell" )
                        , ( "hidden" , Boolean False )
                        , ( "pwls" , Number (6 % 1) )
                        , ( "link_flair_css_class" , Null )
                        , ( "downs" , Number (0 % 1) )
                        , ( "hide_score" , Boolean False )
                        , ( "name" , String "t3_gazovx" )
                        , ( "quarantine" , Boolean False )
                        , ( "link_flair_text_color" , String "dark" )
                        , ( "upvote_ratio" , Number (1 % 1) )
                        , ( "author_flair_background_color" , Null )
                        , ( "subreddit_type" , String "public" )
                        , ( "ups" , Number (20 % 1) )
                        , ( "total_awards_received" , Number (0 % 1) )
                        , ( "media_embed" , Object [] )
                        , ( "author_flair_template_id" , Null )
                        , ( "is_original_content" , Boolean False )
                        , ( "user_reports" , Array [] )
                        , ( "secure_media" , Null )
                        , ( "is_reddit_media_domain" , Boolean False )
                        , ( "is_meta" , Boolean False )
                        , ( "category" , Null )
                        , ( "secure_media_embed" , Object [] )
                        , ( "link_flair_text" , Null )
                        , ( "can_mod_post" , Boolean False )
                        , ( "score" , Number (20 % 1) )
                        , ( "approved_by" , Null )
                        , ( "author_premium" , Boolean True )
                        , ( "thumbnail" , String "" )
                        , ( "edited" , Boolean False )
                        , ( "author_flair_css_class" , Null )
                        , ( "author_flair_richtext" , Array [] )
                        , ( "gildings" , Object [] )
                        , ( "content_categories" , Null )
                        , ( "is_self" , Boolean True )
                        , ( "mod_note" , Null )
                        , ( "created" , Number (1588295176 % 1) )
                        , ( "link_flair_type" , String "text" )
                        , ( "wls" , Number (6 % 1) )
                        , ( "removed_by_category" , Null )
                        , ( "banned_by" , Null )
                        , ( "author_flair_type" , String "text" )
                        , ( "domain" , String "self.haskell" )
                        , ( "allow_live_comments" , Boolean False )
                        , ( "selftext_html"
                          , String
                              "&lt;!-- SC_OFF --&gt;&lt;div class=\\\"md\\\"&gt;&lt;p&gt;This is your opportunity to ask any questions you feel don&amp;#39;t deserve their own threads, no matter how small or simple they might be!&lt;/p&gt;\\n&lt;/div&gt;&lt;!-- SC_ON --&gt;"
                          )
                        , ( "likes" , Null )
                        , ( "suggested_sort" , String "new" )
                        , ( "banned_at_utc" , Null )
                        , ( "view_count" , Null )
                        , ( "archived" , Boolean False )
                        , ( "no_follow" , Boolean True )
                        , ( "is_crosspostable" , Boolean False )
                        , ( "pinned" , Boolean False )
                        , ( "over_18" , Boolean False )
                        , ( "all_awardings" , Array [] )
                        , ( "awarders" , Array [] )
                        , ( "media_only" , Boolean False )
                        , ( "can_gild" , Boolean False )
                        , ( "spoiler" , Boolean False )
                        , ( "locked" , Boolean False )
                        , ( "author_flair_text" , Null )
                        , ( "treatment_tags" , Array [] )
                        , ( "visited" , Boolean False )
                        , ( "removed_by" , Null )
                        , ( "num_reports" , Null )
                        , ( "distinguished" , String "moderator" )
                        , ( "subreddit_id" , String "t5_2qh36" )
                        , ( "mod_reason_by" , Null )
                        , ( "removal_reason" , Null )
                        , ( "link_flair_background_color" , String "" )
                        , ( "id" , String "gazovx" )
                        , ( "is_robot_indexable" , Boolean True )
                        , ( "report_reasons" , Null )
                        , ( "author" , String "AutoModerator" )
                        , ( "discussion_type" , Null )
                        , ( "num_comments" , Number (228 % 1) )
                        , ( "send_replies" , Boolean False )
                        , ( "whitelist_status" , String "all_ads" )
                        , ( "contest_mode" , Boolean False )
                        , ( "mod_reports" , Array [] )
                        , ( "author_patreon_flair" , Boolean False )
                        , ( "author_flair_text_color" , Null )
                        , ( "permalink"
                          , String
                              "/r/haskell/comments/gazovx/monthly_hask_anything_may_2020/"
                          )
                        , ( "parent_whitelist_status" , String "all_ads" )
                        , ( "stickied" , Boolean True )
                        , ( "url"
                          , String
                              "https://old.reddit.com/r/haskell/comments/gazovx/monthly_hask_anything_may_2020/"
                          )
                        , ( "subreddit_subscribers" , Number (55194 % 1) )
                        , ( "created_utc" , Number (1588266376 % 1) )
                        , ( "num_crossposts" , Number (0 % 1) )
                        , ( "media" , Null )
                        , ( "is_video" , Boolean False )
                        ]
                    )
                  ]
              , Object
                  [ ( "kind" , String "t3" )
                  , ( "data"
                    , Object
                        [ ( "approved_at_utc" , Null )
                        , ( "subreddit" , String "haskell" )
                        , ( "selftext" , String "" )
                        , ( "author_fullname" , String "t2_4iein" )
                        , ( "saved" , Boolean False )
                        , ( "mod_reason_title" , Null )
                        , ( "gilded" , Number (0 % 1) )
                        , ( "clicked" , Boolean False )
                        , ( "title"
                          , String "Haskell Error Message, and How to Improve Them"
                          )
                        , ( "link_flair_richtext" , Array [] )
                        , ( "subreddit_name_prefixed" , String "r/haskell" )
                        , ( "hidden" , Boolean False )
                        , ( "pwls" , Number (6 % 1) )
                        , ( "link_flair_css_class" , Null )
                        , ( "downs" , Number (0 % 1) )
                        , ( "hide_score" , Boolean False )
                        , ( "name" , String "t3_gnblom" )
                        , ( "quarantine" , Boolean False )
                        , ( "link_flair_text_color" , String "dark" )
                        , ( "upvote_ratio" , Number (8106479329266893 % 9007199254740992) )
                        , ( "author_flair_background_color" , Null )
                        , ( "subreddit_type" , String "public" )
                        , ( "ups" , Number (35 % 1) )
                        , ( "total_awards_received" , Number (0 % 1) )
                        , ( "media_embed" , Object [] )
                        , ( "author_flair_template_id" , Null )
                        , ( "is_original_content" , Boolean False )
                        , ( "user_reports" , Array [] )
                        , ( "secure_media" , Null )
                        , ( "is_reddit_media_domain" , Boolean False )
                        , ( "is_meta" , Boolean False )
                        , ( "category" , Null )
                        , ( "secure_media_embed" , Object [] )
                        , ( "link_flair_text" , Null )
                        , ( "can_mod_post" , Boolean False )
                        , ( "score" , Number (35 % 1) )
                        , ( "approved_by" , Null )
                        , ( "author_premium" , Boolean False )
                        , ( "thumbnail" , String "" )
                        , ( "edited" , Boolean False )
                        , ( "author_flair_css_class" , Null )
                        , ( "author_flair_richtext" , Array [] )
                        , ( "gildings" , Object [] )
                        , ( "content_categories" , Null )
                        , ( "is_self" , Boolean False )
                        , ( "mod_note" , Null )
                        , ( "created" , Number (1590011148 % 1) )
                        , ( "link_flair_type" , String "text" )
                        , ( "wls" , Number (6 % 1) )
                        , ( "removed_by_category" , Null )
                        , ( "banned_by" , Null )
                        , ( "author_flair_type" , String "text" )
                        , ( "domain" , String "anthony.noided.media" )
                        , ( "allow_live_comments" , Boolean False )
                        , ( "selftext_html" , Null )
                        , ( "likes" , Null )
                        , ( "suggested_sort" , Null )
                        , ( "banned_at_utc" , Null )
                        , ( "view_count" , Null )
                        , ( "archived" , Boolean False )
                        , ( "no_follow" , Boolean False )
                        , ( "is_crosspostable" , Boolean False )
                        , ( "pinned" , Boolean False )
                        , ( "over_18" , Boolean False )
                        , ( "all_awardings" , Array [] )
                        , ( "awarders" , Array [] )
                        , ( "media_only" , Boolean False )
                        , ( "can_gild" , Boolean False )
                        , ( "spoiler" , Boolean False )
                        , ( "locked" , Boolean False )
                        , ( "author_flair_text" , Null )
                        , ( "treatment_tags" , Array [] )
                        , ( "visited" , Boolean False )
                        , ( "removed_by" , Null )
                        , ( "num_reports" , Null )
                        , ( "distinguished" , Null )
                        , ( "subreddit_id" , String "t5_2qh36" )
                        , ( "mod_reason_by" , Null )
                        , ( "removal_reason" , Null )
                        , ( "link_flair_background_color" , String "" )
                        , ( "id" , String "gnblom" )
                        , ( "is_robot_indexable" , Boolean True )
                        , ( "report_reasons" , Null )
                        , ( "author" , String "THeShinyHObbiest" )
                        , ( "discussion_type" , Null )
                        , ( "num_comments" , Number (32 % 1) )
                        , ( "send_replies" , Boolean True )
                        , ( "whitelist_status" , String "all_ads" )
                        , ( "contest_mode" , Boolean False )
                        , ( "mod_reports" , Array [] )
                        , ( "author_patreon_flair" , Boolean False )
                        , ( "author_flair_text_color" , Null )
                        , ( "permalink"
                          , String
                              "/r/haskell/comments/gnblom/haskell_error_message_and_how_to_improve_them/"
                          )
                        , ( "parent_whitelist_status" , String "all_ads" )
                        , ( "stickied" , Boolean False )
                        , ( "url"
                          , String
                              "https://anthony.noided.media/blog/haskell/programming/2020/05/14/haskell-errors.html"
                          )
                        , ( "subreddit_subscribers" , Number (55194 % 1) )
                        , ( "created_utc" , Number (1589982348 % 1) )
                        , ( "num_crossposts" , Number (0 % 1) )
                        , ( "media" , Null )
                        , ( "is_video" , Boolean False )
                        ]
                    )
                  ]
              , Object
                  [ ( "kind" , String "t3" )
                  , ( "data"
                    , Object
                        [ ( "approved_at_utc" , Null )
                        , ( "subreddit" , String "haskell" )
                        , ( "selftext"
                          , String
                              "Hello dear redditors,\\n\\nI'm happy to announce my book \\\"Functional Design and Architecture\\\".\\n\\nIt's 80% done (8 chapters of 10, 600k symbols), and I decided to start selling it via Leanpub because it's already the most comprehensive guide on building of real software in Haskell and in FP.\\n\\n[Functional Design and Architecture (book) on Leanpub](https://leanpub.com/functional-design-and-architecture)\\n\\nThe book is focussing on many different design patterns, design principles and approaches, but the central role in it plays the approach I call Hierarchical Free Monads. Although the draft of chapters is available online [here](https://graninas.com/functional-design-and-architecture-book/), I won't be uncovering the rest, at least for now. I spent more than 2 years of writing the book, developing the approaches, providing materials and creating showcase projects. And now I think it's not an exaggeration to say that my Hierarchical Free Monads is the most developed approach in Haskell today.\\n\\nThe book is based on 2 projects, so you can play with the concepts easily:\\n\\n* [Hydra](https://github.com/graninas/Hydra), a full-fledged framework for building web services, multithreaded and concurrent applications with SQL and KV DB support. Contains 3 engines: Final Tagless, Free Monad and Church Encoded Free Monad, as well as several demo applications to compare these 3 approaches.\\n* [Andromeda](https://github.com/graninas/Andromeda), a SCADA software for spaceship control.\\n\\nI also have a Patreon program for the book:\\n\\n[Patreon: \\\"Functional Design and Architecture\\\"](https://www.patreon.com/functional_design_and_architecture)\\n\\nAll the money collected from this program will be used to hire professional editors, designers, reviewers. I'm very grateful to all my Patron supporters! The supporters have an access to some exclusive content. They will get a edited book as well.\\n\\nThe following project is of my design also.\\n\\n* [Node](https://github.com/graninas/Node), a real-world all-in-one framework which is tested in production. It allows to build network actors and blockchain protocols, console applications, work with KV database and cryptography. Sample but not simple blockchain applications are also provided there.\\n\\nYou can get familiar with my long read articles explaining the concepts in details:\\n\\n* [Hierarchical Free Monads: The Most Developed Approach In Haskell (article)](https://github.com/graninas/hierarchical-free-monads-the-most-developed-approach-in-haskell)\\n* [Automatic White-Box Testing with Free Monads (article, showcase)](https://github.com/graninas/automatic-whitebox-testing-showcase)\\n* [Building network actors with Node Framework](https://gist.github.com/graninas/9beb8df5d88dda5fa21c47ce9bcb0e16)\\n\\nYou might also want to get familiar with my [list of materials on Software Design in Haskell](https://github.com/graninas/software-design-in-haskell).\\n\\nI'm also giving talks on this topic. Consider the following talks:\\n\\n* [Hierarchical Free Monads and Software Design in Functional Programming (talk)](https://www.youtube.com/watch?v=3GKQ4ni2pS0)\\n* [Automatic Whitebox Testing with Free Monads (talk)](https://www.youtube.com/watch?v=ciZL-adDpVQ)\\n* [Final Tagless vs Free Monads (talk, Russian)](https://www.youtube.com/watch?v=u1GGqDQyGfc) | [slides (English)](https://drive.google.com/open?id=1VhS8ySgk2w5RoN_l_Ar_axcE4Dzf97zLw1uuzUJQbCo)\\n\\nAnd this list of my materials is not even complete. For the record, I used Free Monads for making my own STM library: in Haskell and in C++. The implementation was incredibly simple due to the power of Free Monads to abstract things. There are different projects:\\n\\n* [stm-free](https://github.com/graninas/stm-free), my Free Monad based STM library in Haskell;\\n* [cpp\\\\_stm-free](https://github.com/graninas/cpp_stm_free), the port to C++. Even more, it has 2 independent engines: Free Monad based and Church Encoded Free Monad based.\\n* [Software Transactional Memory in C++: pure functional approach (Tutorial)](https://gist.github.com/graninas/c7e0a603f3a22c7e85daa4599bf92525) \\\\- the article, in case you like strange functional programming in C++.\\n* [Functional Approach To Software Transactional Memory in C++ (talk, Russian)](https://www.youtube.com/watch?v=VHZPcz8HwZs) | [slides](https://docs.google.com/presentation/d/1_znOLZDKruKRNLA58TDlnXYQjTg9sXNJHPOLHfDTjeU/edit?usp=sharing) (English)\\n* [cpp\\\\_parsec\\\\_free](https://github.com/graninas/cpp_parsec_free): a PoC of monadic parsers in C++ based on the same idea of Free Monads.\\n* [Monadic Parsers in C++ (talk, Russian)](https://www.youtube.com/watch?v=q39PHTJDaLE) | [slides](https://docs.google.com/presentation/d/1zlwKBX8-DYVWUYmzvmKm7ggDVBugEJzY6OFSWjeQOA4/edit?usp=sharing) (English)\\n* [hinteractive](https://github.com/graninas/hinteractive), an eDSL-like engine for interactive fiction games like Zork. Free Monad based.\\n\\nYes, all these projects show that I investigated Free Monads from all possible sides. But even more, there are two open source frameworks I (with my coworkers) designed for our employer, and these projects are heavily used in production:\\n\\n* [PureScript Presto](https://github.com/juspay/purescript-presto) \\\\- a framework for building mobile apps using a handy eDSL.\\n* [PureScript Presto.Backend](https://github.com/juspay/purescript-presto-backend) \\\\- a framework for web RESTful backends.\\n\\nStill not convinced? Follow me ([Twitter](https://twitter.com/graninas), [GitHub](https://github.com/graninas), [LinkedIn](https://www.linkedin.com/in/alexander-granin-46889236/), [Telegram](https://web.telegram.org/#/im?p=@graninas), [Facebook](https://www.facebook.com/alexandr.granin)), hire me, and keep your eyes on my activity. Even more materials are coming!\\n\\nYours truly,\\n\\nAlexander Granin"
                          )
                        , ( "author_fullname" , String "t2_geqys" )
                        , ( "saved" , Boolean False )
                        , ( "mod_reason_title" , Null )
                        , ( "gilded" , Number (0 % 1) )
                        , ( "clicked" , Boolean False )
                        , ( "title"
                          , String "Book \\\"Functional Design and Architecture\\\""
                          )
                        , ( "link_flair_richtext" , Array [] )
                        , ( "subreddit_name_prefixed" , String "r/haskell" )
                        , ( "hidden" , Boolean False )
                        , ( "pwls" , Number (6 % 1) )
                        , ( "link_flair_css_class" , Null )
                        , ( "downs" , Number (0 % 1) )
                        , ( "hide_score" , Boolean False )
                        , ( "name" , String "t3_gmxfqz" )
                        , ( "quarantine" , Boolean False )
                        , ( "link_flair_text_color" , String "dark" )
                        , ( "upvote_ratio" , Number (4368491638549381 % 4503599627370496) )
                        , ( "author_flair_background_color" , Null )
                        , ( "subreddit_type" , String "public" )
                        , ( "ups" , Number (155 % 1) )
                        , ( "total_awards_received" , Number (1 % 1) )
                        , ( "media_embed" , Object [] )
                        , ( "author_flair_template_id" , Null )
                        , ( "is_original_content" , Boolean False )
                        , ( "user_reports" , Array [] )
                        , ( "secure_media" , Null )
                        , ( "is_reddit_media_domain" , Boolean False )
                        , ( "is_meta" , Boolean False )
                        , ( "category" , Null )
                        , ( "secure_media_embed" , Object [] )
                        , ( "link_flair_text" , Null )
                        , ( "can_mod_post" , Boolean False )
                        , ( "score" , Number (155 % 1) )
                        , ( "approved_by" , Null )
                        , ( "author_premium" , Boolean False )
                        , ( "thumbnail" , String "" )
                        , ( "edited" , Number (1589979013 % 1) )
                        , ( "author_flair_css_class" , Null )
                        , ( "author_flair_richtext" , Array [] )
                        , ( "gildings" , Object [] )
                        , ( "content_categories" , Null )
                        , ( "is_self" , Boolean True )
                        , ( "mod_note" , Null )
                        , ( "created" , Number (1589951620 % 1) )
                        , ( "link_flair_type" , String "text" )
                        , ( "wls" , Number (6 % 1) )
                        , ( "removed_by_category" , Null )
                        , ( "banned_by" , Null )
                        , ( "author_flair_type" , String "text" )
                        , ( "domain" , String "self.haskell" )
                        , ( "allow_live_comments" , Boolean False )
                        , ( "selftext_html"
                          , String
                              "&lt;!-- SC_OFF --&gt;&lt;div class=\\\"md\\\"&gt;&lt;p&gt;Hello dear redditors,&lt;/p&gt;\\n\\n&lt;p&gt;I&amp;#39;m happy to announce my book &amp;quot;Functional Design and Architecture&amp;quot;.&lt;/p&gt;\\n\\n&lt;p&gt;It&amp;#39;s 80% done (8 chapters of 10, 600k symbols), and I decided to start selling it via Leanpub because it&amp;#39;s already the most comprehensive guide on building of real software in Haskell and in FP.&lt;/p&gt;\\n\\n&lt;p&gt;&lt;a href=\\\"https://leanpub.com/functional-design-and-architecture\\\"&gt;Functional Design and Architecture (book) on Leanpub&lt;/a&gt;&lt;/p&gt;\\n\\n&lt;p&gt;The book is focussing on many different design patterns, design principles and approaches, but the central role in it plays the approach I call Hierarchical Free Monads. Although the draft of chapters is available online &lt;a href=\\\"https://graninas.com/functional-design-and-architecture-book/\\\"&gt;here&lt;/a&gt;, I won&amp;#39;t be uncovering the rest, at least for now. I spent more than 2 years of writing the book, developing the approaches, providing materials and creating showcase projects. And now I think it&amp;#39;s not an exaggeration to say that my Hierarchical Free Monads is the most developed approach in Haskell today.&lt;/p&gt;\\n\\n&lt;p&gt;The book is based on 2 projects, so you can play with the concepts easily:&lt;/p&gt;\\n\\n&lt;ul&gt;\\n&lt;li&gt;&lt;a href=\\\"https://github.com/graninas/Hydra\\\"&gt;Hydra&lt;/a&gt;, a full-fledged framework for building web services, multithreaded and concurrent applications with SQL and KV DB support. Contains 3 engines: Final Tagless, Free Monad and Church Encoded Free Monad, as well as several demo applications to compare these 3 approaches.&lt;/li&gt;\\n&lt;li&gt;&lt;a href=\\\"https://github.com/graninas/Andromeda\\\"&gt;Andromeda&lt;/a&gt;, a SCADA software for spaceship control.&lt;/li&gt;\\n&lt;/ul&gt;\\n\\n&lt;p&gt;I also have a Patreon program for the book:&lt;/p&gt;\\n\\n&lt;p&gt;&lt;a href=\\\"https://www.patreon.com/functional_design_and_architecture\\\"&gt;Patreon: &amp;quot;Functional Design and Architecture&amp;quot;&lt;/a&gt;&lt;/p&gt;\\n\\n&lt;p&gt;All the money collected from this program will be used to hire professional editors, designers, reviewers. I&amp;#39;m very grateful to all my Patron supporters! The supporters have an access to some exclusive content. They will get a edited book as well.&lt;/p&gt;\\n\\n&lt;p&gt;The following project is of my design also.&lt;/p&gt;\\n\\n&lt;ul&gt;\\n&lt;li&gt;&lt;a href=\\\"https://github.com/graninas/Node\\\"&gt;Node&lt;/a&gt;, a real-world all-in-one framework which is tested in production. It allows to build network actors and blockchain protocols, console applications, work with KV database and cryptography. Sample but not simple blockchain applications are also provided there.&lt;/li&gt;\\n&lt;/ul&gt;\\n\\n&lt;p&gt;You can get familiar with my long read articles explaining the concepts in details:&lt;/p&gt;\\n\\n&lt;ul&gt;\\n&lt;li&gt;&lt;a href=\\\"https://github.com/graninas/hierarchical-free-monads-the-most-developed-approach-in-haskell\\\"&gt;Hierarchical Free Monads: The Most Developed Approach In Haskell (article)&lt;/a&gt;&lt;/li&gt;\\n&lt;li&gt;&lt;a href=\\\"https://github.com/graninas/automatic-whitebox-testing-showcase\\\"&gt;Automatic White-Box Testing with Free Monads (article, showcase)&lt;/a&gt;&lt;/li&gt;\\n&lt;li&gt;&lt;a href=\\\"https://gist.github.com/graninas/9beb8df5d88dda5fa21c47ce9bcb0e16\\\"&gt;Building network actors with Node Framework&lt;/a&gt;&lt;/li&gt;\\n&lt;/ul&gt;\\n\\n&lt;p&gt;You might also want to get familiar with my &lt;a href=\\\"https://github.com/graninas/software-design-in-haskell\\\"&gt;list of materials on Software Design in Haskell&lt;/a&gt;.&lt;/p&gt;\\n\\n&lt;p&gt;I&amp;#39;m also giving talks on this topic. Consider the following talks:&lt;/p&gt;\\n\\n&lt;ul&gt;\\n&lt;li&gt;&lt;a href=\\\"https://www.youtube.com/watch?v=3GKQ4ni2pS0\\\"&gt;Hierarchical Free Monads and Software Design in Functional Programming (talk)&lt;/a&gt;&lt;/li&gt;\\n&lt;li&gt;&lt;a href=\\\"https://www.youtube.com/watch?v=ciZL-adDpVQ\\\"&gt;Automatic Whitebox Testing with Free Monads (talk)&lt;/a&gt;&lt;/li&gt;\\n&lt;li&gt;&lt;a href=\\\"https://www.youtube.com/watch?v=u1GGqDQyGfc\\\"&gt;Final Tagless vs Free Monads (talk, Russian)&lt;/a&gt; | &lt;a href=\\\"https://drive.google.com/open?id=1VhS8ySgk2w5RoN_l_Ar_axcE4Dzf97zLw1uuzUJQbCo\\\"&gt;slides (English)&lt;/a&gt;&lt;/li&gt;\\n&lt;/ul&gt;\\n\\n&lt;p&gt;And this list of my materials is not even complete. For the record, I used Free Monads for making my own STM library: in Haskell and in C++. The implementation was incredibly simple due to the power of Free Monads to abstract things. There are different projects:&lt;/p&gt;\\n\\n&lt;ul&gt;\\n&lt;li&gt;&lt;a href=\\\"https://github.com/graninas/stm-free\\\"&gt;stm-free&lt;/a&gt;, my Free Monad based STM library in Haskell;&lt;/li&gt;\\n&lt;li&gt;&lt;a href=\\\"https://github.com/graninas/cpp_stm_free\\\"&gt;cpp_stm-free&lt;/a&gt;, the port to C++. Even more, it has 2 independent engines: Free Monad based and Church Encoded Free Monad based.&lt;/li&gt;\\n&lt;li&gt;&lt;a href=\\\"https://gist.github.com/graninas/c7e0a603f3a22c7e85daa4599bf92525\\\"&gt;Software Transactional Memory in C++: pure functional approach (Tutorial)&lt;/a&gt; - the article, in case you like strange functional programming in C++.&lt;/li&gt;\\n&lt;li&gt;&lt;a href=\\\"https://www.youtube.com/watch?v=VHZPcz8HwZs\\\"&gt;Functional Approach To Software Transactional Memory in C++ (talk, Russian)&lt;/a&gt; | &lt;a href=\\\"https://docs.google.com/presentation/d/1_znOLZDKruKRNLA58TDlnXYQjTg9sXNJHPOLHfDTjeU/edit?usp=sharing\\\"&gt;slides&lt;/a&gt; (English)&lt;/li&gt;\\n&lt;li&gt;&lt;a href=\\\"https://github.com/graninas/cpp_parsec_free\\\"&gt;cpp_parsec_free&lt;/a&gt;: a PoC of monadic parsers in C++ based on the same idea of Free Monads.&lt;/li&gt;\\n&lt;li&gt;&lt;a href=\\\"https://www.youtube.com/watch?v=q39PHTJDaLE\\\"&gt;Monadic Parsers in C++ (talk, Russian)&lt;/a&gt; | &lt;a href=\\\"https://docs.google.com/presentation/d/1zlwKBX8-DYVWUYmzvmKm7ggDVBugEJzY6OFSWjeQOA4/edit?usp=sharing\\\"&gt;slides&lt;/a&gt; (English)&lt;/li&gt;\\n&lt;li&gt;&lt;a href=\\\"https://github.com/graninas/hinteractive\\\"&gt;hinteractive&lt;/a&gt;, an eDSL-like engine for interactive fiction games like Zork. Free Monad based.&lt;/li&gt;\\n&lt;/ul&gt;\\n\\n&lt;p&gt;Yes, all these projects show that I investigated Free Monads from all possible sides. But even more, there are two open source frameworks I (with my coworkers) designed for our employer, and these projects are heavily used in production:&lt;/p&gt;\\n\\n&lt;ul&gt;\\n&lt;li&gt;&lt;a href=\\\"https://github.com/juspay/purescript-presto\\\"&gt;PureScript Presto&lt;/a&gt; - a framework for building mobile apps using a handy eDSL.&lt;/li&gt;\\n&lt;li&gt;&lt;a href=\\\"https://github.com/juspay/purescript-presto-backend\\\"&gt;PureScript Presto.Backend&lt;/a&gt; - a framework for web RESTful backends.&lt;/li&gt;\\n&lt;/ul&gt;\\n\\n&lt;p&gt;Still not convinced? Follow me (&lt;a href=\\\"https://twitter.com/graninas\\\"&gt;Twitter&lt;/a&gt;, &lt;a href=\\\"https://github.com/graninas\\\"&gt;GitHub&lt;/a&gt;, &lt;a href=\\\"https://www.linkedin.com/in/alexander-granin-46889236/\\\"&gt;LinkedIn&lt;/a&gt;, &lt;a href=\\\"https://web.telegram.org/#/im?p=@graninas\\\"&gt;Telegram&lt;/a&gt;, &lt;a href=\\\"https://www.facebook.com/alexandr.granin\\\"&gt;Facebook&lt;/a&gt;), hire me, and keep your eyes on my activity. Even more materials are coming!&lt;/p&gt;\\n\\n&lt;p&gt;Yours truly,&lt;/p&gt;\\n\\n&lt;p&gt;Alexander Granin&lt;/p&gt;\\n&lt;/div&gt;&lt;!-- SC_ON --&gt;"
                          )
                        , ( "likes" , Null )
                        , ( "suggested_sort" , Null )
                        , ( "banned_at_utc" , Null )
                        , ( "view_count" , Null )
                        , ( "archived" , Boolean False )
                        , ( "no_follow" , Boolean False )
                        , ( "is_crosspostable" , Boolean False )
                        , ( "pinned" , Boolean False )
                        , ( "over_18" , Boolean False )
                        , ( "all_awardings"
                          , Array
                              [ Object
                                  [ ( "giver_coin_reward" , Null )
                                  , ( "subreddit_id" , Null )
                                  , ( "is_new" , Boolean False )
                                  , ( "days_of_drip_extension" , Number (0 % 1) )
                                  , ( "coin_price" , Number (500 % 1) )
                                  , ( "id" , String "award_43c43a35-15c5-4f73-91ef-fe538426435a" )
                                  , ( "penny_donate" , Null )
                                  , ( "coin_reward" , Number (100 % 1) )
                                  , ( "icon_url"
                                    , String
                                        "https://i.redd.it/award_images/t5_22cerq/xe5mw55w5v541_BlessUp.png"
                                    )
                                  , ( "days_of_premium" , Number (0 % 1) )
                                  , ( "icon_height" , Number (2048 % 1) )
                                  , ( "resized_icons"
                                    , Array
                                        [ Object
                                            [ ( "url"
                                              , String
                                                  "https://preview.redd.it/award_images/t5_22cerq/xe5mw55w5v541_BlessUp.png?width=16&amp;height=16&amp;auto=webp&amp;s=e84e08de4b1352e679d612c063584341f56bc2b5"
                                              )
                                            , ( "width" , Number (16 % 1) )
                                            , ( "height" , Number (16 % 1) )
                                            ]
                                        , Object
                                            [ ( "url"
                                              , String
                                                  "https://preview.redd.it/award_images/t5_22cerq/xe5mw55w5v541_BlessUp.png?width=32&amp;height=32&amp;auto=webp&amp;s=d01d7a3286bb55c235e217736c78c66e2d7d0c18"
                                              )
                                            , ( "width" , Number (32 % 1) )
                                            , ( "height" , Number (32 % 1) )
                                            ]
                                        , Object
                                            [ ( "url"
                                              , String
                                                  "https://preview.redd.it/award_images/t5_22cerq/xe5mw55w5v541_BlessUp.png?width=48&amp;height=48&amp;auto=webp&amp;s=6ae7d390be614e44f1ec06141d0ba51d65494bff"
                                              )
                                            , ( "width" , Number (48 % 1) )
                                            , ( "height" , Number (48 % 1) )
                                            ]
                                        , Object
                                            [ ( "url"
                                              , String
                                                  "https://preview.redd.it/award_images/t5_22cerq/xe5mw55w5v541_BlessUp.png?width=64&amp;height=64&amp;auto=webp&amp;s=1c88befd3d95c2ea37b95a7132db98d8a8730ae1"
                                              )
                                            , ( "width" , Number (64 % 1) )
                                            , ( "height" , Number (64 % 1) )
                                            ]
                                        , Object
                                            [ ( "url"
                                              , String
                                                  "https://preview.redd.it/award_images/t5_22cerq/xe5mw55w5v541_BlessUp.png?width=128&amp;height=128&amp;auto=webp&amp;s=f97d6987f6545f6cb659f1fce7c304278a92f762"
                                              )
                                            , ( "width" , Number (128 % 1) )
                                            , ( "height" , Number (128 % 1) )
                                            ]
                                        ]
                                    )
                                  , ( "icon_width" , Number (2048 % 1) )
                                  , ( "start_date" , Null )
                                  , ( "is_enabled" , Boolean True )
                                  , ( "description"
                                    , String
                                        "Prayers up for the blessed. Gives %{coin_symbol}100 Coins to both the author and the community."
                                    )
                                  , ( "end_date" , Null )
                                  , ( "subreddit_coin_reward" , Number (100 % 1) )
                                  , ( "count" , Number (1 % 1) )
                                  , ( "name" , String "Bless Up (Pro)" )
                                  , ( "icon_format" , Null )
                                  , ( "award_sub_type" , String "GLOBAL" )
                                  , ( "penny_price" , Null )
                                  , ( "award_type" , String "global" )
                                  ]
                              ]
                          )
                        , ( "awarders" , Array [] )
                        , ( "media_only" , Boolean False )
                        , ( "can_gild" , Boolean False )
                        , ( "spoiler" , Boolean False )
                        , ( "locked" , Boolean False )
                        , ( "author_flair_text" , Null )
                        , ( "treatment_tags" , Array [] )
                        , ( "visited" , Boolean False )
                        , ( "removed_by" , Null )
                        , ( "num_reports" , Null )
                        , ( "distinguished" , Null )
                        , ( "subreddit_id" , String "t5_2qh36" )
                        , ( "mod_reason_by" , Null )
                        , ( "removal_reason" , Null )
                        , ( "link_flair_background_color" , String "" )
                        , ( "id" , String "gmxfqz" )
                        , ( "is_robot_indexable" , Boolean True )
                        , ( "report_reasons" , Null )
                        , ( "author" , String "graninas" )
                        , ( "discussion_type" , Null )
                        , ( "num_comments" , Number (26 % 1) )
                        , ( "send_replies" , Boolean True )
                        , ( "whitelist_status" , String "all_ads" )
                        , ( "contest_mode" , Boolean False )
                        , ( "mod_reports" , Array [] )
                        , ( "author_patreon_flair" , Boolean False )
                        , ( "author_flair_text_color" , Null )
                        , ( "permalink"
                          , String
                              "/r/haskell/comments/gmxfqz/book_functional_design_and_architecture/"
                          )
                        , ( "parent_whitelist_status" , String "all_ads" )
                        , ( "stickied" , Boolean False )
                        , ( "url"
                          , String
                              "https://old.reddit.com/r/haskell/comments/gmxfqz/book_functional_design_and_architecture/"
                          )
                        , ( "subreddit_subscribers" , Number (55194 % 1) )
                        , ( "created_utc" , Number (1589922820 % 1) )
                        , ( "num_crossposts" , Number (2 % 1) )
                        , ( "media" , Null )
                        , ( "is_video" , Boolean False )
                        ]
                    )
                  ]
              , Object
                  [ ( "kind" , String "t3" )
                  , ( "data"
                    , Object
                        [ ( "approved_at_utc" , Null )
                        , ( "subreddit" , String "haskell" )
                        , ( "selftext" , String "" )
                        , ( "author_fullname" , String "t2_3qjdu" )
                        , ( "saved" , Boolean False )
                        , ( "mod_reason_title" , Null )
                        , ( "gilded" , Number (0 % 1) )
                        , ( "clicked" , Boolean False )
                        , ( "title" , String "DerivingVia sums-of-products" )
                        , ( "link_flair_richtext" , Array [] )
                        , ( "subreddit_name_prefixed" , String "r/haskell" )
                        , ( "hidden" , Boolean False )
                        , ( "pwls" , Number (6 % 1) )
                        , ( "link_flair_css_class" , Null )
                        , ( "downs" , Number (0 % 1) )
                        , ( "hide_score" , Boolean False )
                        , ( "name" , String "t3_gn8c5r" )
                        , ( "quarantine" , Boolean False )
                        , ( "link_flair_text_color" , String "dark" )
                        , ( "upvote_ratio" , Number (1 % 1) )
                        , ( "author_flair_background_color" , Null )
                        , ( "subreddit_type" , String "public" )
                        , ( "ups" , Number (17 % 1) )
                        , ( "total_awards_received" , Number (0 % 1) )
                        , ( "media_embed" , Object [] )
                        , ( "author_flair_template_id" , Null )
                        , ( "is_original_content" , Boolean False )
                        , ( "user_reports" , Array [] )
                        , ( "secure_media" , Null )
                        , ( "is_reddit_media_domain" , Boolean False )
                        , ( "is_meta" , Boolean False )
                        , ( "category" , Null )
                        , ( "secure_media_embed" , Object [] )
                        , ( "link_flair_text" , Null )
                        , ( "can_mod_post" , Boolean False )
                        , ( "score" , Number (17 % 1) )
                        , ( "approved_by" , Null )
                        , ( "author_premium" , Boolean False )
                        , ( "thumbnail" , String "" )
                        , ( "edited" , Boolean False )
                        , ( "author_flair_css_class" , Null )
                        , ( "author_flair_richtext" , Array [] )
                        , ( "gildings" , Object [] )
                        , ( "content_categories" , Null )
                        , ( "is_self" , Boolean False )
                        , ( "mod_note" , Null )
                        , ( "created" , Number (1589996118 % 1) )
                        , ( "link_flair_type" , String "text" )
                        , ( "wls" , Number (6 % 1) )
                        , ( "removed_by_category" , Null )
                        , ( "banned_by" , Null )
                        , ( "author_flair_type" , String "text" )
                        , ( "domain" , String "iceland_jack.brick.do" )
                        , ( "allow_live_comments" , Boolean False )
                        , ( "selftext_html" , Null )
                        , ( "likes" , Null )
                        , ( "suggested_sort" , Null )
                        , ( "banned_at_utc" , Null )
                        , ( "view_count" , Null )
                        , ( "archived" , Boolean False )
                        , ( "no_follow" , Boolean False )
                        , ( "is_crosspostable" , Boolean False )
                        , ( "pinned" , Boolean False )
                        , ( "over_18" , Boolean False )
                        , ( "all_awardings" , Array [] )
                        , ( "awarders" , Array [] )
                        , ( "media_only" , Boolean False )
                        , ( "can_gild" , Boolean False )
                        , ( "spoiler" , Boolean False )
                        , ( "locked" , Boolean False )
                        , ( "author_flair_text" , Null )
                        , ( "treatment_tags" , Array [] )
                        , ( "visited" , Boolean False )
                        , ( "removed_by" , Null )
                        , ( "num_reports" , Null )
                        , ( "distinguished" , Null )
                        , ( "subreddit_id" , String "t5_2qh36" )
                        , ( "mod_reason_by" , Null )
                        , ( "removal_reason" , Null )
                        , ( "link_flair_background_color" , String "" )
                        , ( "id" , String "gn8c5r" )
                        , ( "is_robot_indexable" , Boolean True )
                        , ( "report_reasons" , Null )
                        , ( "author" , String "Iceland_jack" )
                        , ( "discussion_type" , Null )
                        , ( "num_comments" , Number (5 % 1) )
                        , ( "send_replies" , Boolean True )
                        , ( "whitelist_status" , String "all_ads" )
                        , ( "contest_mode" , Boolean False )
                        , ( "mod_reports" , Array [] )
                        , ( "author_patreon_flair" , Boolean False )
                        , ( "author_flair_text_color" , Null )
                        , ( "permalink"
                          , String "/r/haskell/comments/gn8c5r/derivingvia_sumsofproducts/"
                          )
                        , ( "parent_whitelist_status" , String "all_ads" )
                        , ( "stickied" , Boolean False )
                        , ( "url"
                          , String
                              "https://iceland_jack.brick.do/e28e745c-40b8-4b0b-8148-1f1ae0c32d43"
                          )
                        , ( "subreddit_subscribers" , Number (55194 % 1) )
                        , ( "created_utc" , Number (1589967318 % 1) )
                        , ( "num_crossposts" , Number (0 % 1) )
                        , ( "media" , Null )
                        , ( "is_video" , Boolean False )
                        ]
                    )
                  ]
              , Object
                  [ ( "kind" , String "t3" )
                  , ( "data"
                    , Object
                        [ ( "approved_at_utc" , Null )
                        , ( "subreddit" , String "haskell" )
                        , ( "selftext" , String "" )
                        , ( "author_fullname" , String "t2_jxviuup" )
                        , ( "saved" , Boolean False )
                        , ( "mod_reason_title" , Null )
                        , ( "gilded" , Number (0 % 1) )
                        , ( "clicked" , Boolean False )
                        , ( "title"
                          , String
                              "Alejandro Serrano Mena on Why Functors and Applicatives Compose but Monads Don't"
                          )
                        , ( "link_flair_richtext" , Array [] )
                        , ( "subreddit_name_prefixed" , String "r/haskell" )
                        , ( "hidden" , Boolean False )
                        , ( "pwls" , Number (6 % 1) )
                        , ( "link_flair_css_class" , Null )
                        , ( "downs" , Number (0 % 1) )
                        , ( "hide_score" , Boolean False )
                        , ( "name" , String "t3_gn2tqs" )
                        , ( "quarantine" , Boolean False )
                        , ( "link_flair_text_color" , String "dark" )
                        , ( "upvote_ratio" , Number (4278419646001971 % 4503599627370496) )
                        , ( "author_flair_background_color" , Null )
                        , ( "subreddit_type" , String "public" )
                        , ( "ups" , Number (47 % 1) )
                        , ( "total_awards_received" , Number (0 % 1) )
                        , ( "media_embed"
                          , Object
                              [ ( "content"
                                , String
                                    "&lt;iframe width=\\\"600\\\" height=\\\"338\\\" src=\\\"https://www.youtube.com/embed/eZ9FpG8May8?feature=oembed&amp;enablejsapi=1\\\" frameborder=\\\"0\\\" allow=\\\"accelerometer; autoplay; encrypted-media; gyroscope; picture-in-picture\\\" allowfullscreen&gt;&lt;/iframe&gt;"
                                )
                              , ( "width" , Number (600 % 1) )
                              , ( "scrolling" , Boolean False )
                              , ( "height" , Number (338 % 1) )
                              ]
                          )
                        , ( "author_flair_template_id" , Null )
                        , ( "is_original_content" , Boolean False )
                        , ( "user_reports" , Array [] )
                        , ( "secure_media"
                          , Object
                              [ ( "type" , String "youtube.com" )
                              , ( "oembed"
                                , Object
                                    [ ( "provider_url" , String "https://www.youtube.com/" )
                                    , ( "version" , String "1.0" )
                                    , ( "title"
                                      , String
                                          "Alejandro Serrano Mena on Why Functors and Applicatives Compose but Monads Don't"
                                      )
                                    , ( "type" , String "video" )
                                    , ( "thumbnail_width" , Number (480 % 1) )
                                    , ( "height" , Number (338 % 1) )
                                    , ( "width" , Number (600 % 1) )
                                    , ( "html"
                                      , String
                                          "&lt;iframe width=\\\"600\\\" height=\\\"338\\\" src=\\\"https://www.youtube.com/embed/eZ9FpG8May8?feature=oembed&amp;enablejsapi=1\\\" frameborder=\\\"0\\\" allow=\\\"accelerometer; autoplay; encrypted-media; gyroscope; picture-in-picture\\\" allowfullscreen&gt;&lt;/iframe&gt;"
                                      )
                                    , ( "author_name"
                                      , String "Berlin Functional Programming Group"
                                      )
                                    , ( "provider_name" , String "YouTube" )
                                    , ( "thumbnail_url"
                                      , String "https://i.ytimg.com/vi/eZ9FpG8May8/hqdefault.jpg"
                                      )
                                    , ( "thumbnail_height" , Number (360 % 1) )
                                    , ( "author_url"
                                      , String
                                          "https://www.youtube.com/channel/UCNp-DVb8cQRIOo32sZhWgNg"
                                      )
                                    ]
                                )
                              ]
                          )
                        , ( "is_reddit_media_domain" , Boolean False )
                        , ( "is_meta" , Boolean False )
                        , ( "category" , Null )
                        , ( "secure_media_embed"
                          , Object
                              [ ( "content"
                                , String
                                    "&lt;iframe width=\\\"600\\\" height=\\\"338\\\" src=\\\"https://www.youtube.com/embed/eZ9FpG8May8?feature=oembed&amp;enablejsapi=1\\\" frameborder=\\\"0\\\" allow=\\\"accelerometer; autoplay; encrypted-media; gyroscope; picture-in-picture\\\" allowfullscreen&gt;&lt;/iframe&gt;"
                                )
                              , ( "width" , Number (600 % 1) )
                              , ( "scrolling" , Boolean False )
                              , ( "media_domain_url"
                                , String "https://www.redditmedia.com/mediaembed/gn2tqs"
                                )
                              , ( "height" , Number (338 % 1) )
                              ]
                          )
                        , ( "link_flair_text" , Null )
                        , ( "can_mod_post" , Boolean False )
                        , ( "score" , Number (47 % 1) )
                        , ( "approved_by" , Null )
                        , ( "author_premium" , Boolean False )
                        , ( "thumbnail" , String "" )
                        , ( "edited" , Boolean False )
                        , ( "author_flair_css_class" , Null )
                        , ( "author_flair_richtext" , Array [] )
                        , ( "gildings" , Object [] )
                        , ( "content_categories" , Null )
                        , ( "is_self" , Boolean False )
                        , ( "mod_note" , Null )
                        , ( "created" , Number (1589970172 % 1) )
                        , ( "link_flair_type" , String "text" )
                        , ( "wls" , Number (6 % 1) )
                        , ( "removed_by_category" , Null )
                        , ( "banned_by" , Null )
                        , ( "author_flair_type" , String "text" )
                        , ( "domain" , String "youtube.com" )
                        , ( "allow_live_comments" , Boolean False )
                        , ( "selftext_html" , Null )
                        , ( "likes" , Null )
                        , ( "suggested_sort" , Null )
                        , ( "banned_at_utc" , Null )
                        , ( "view_count" , Null )
                        , ( "archived" , Boolean False )
                        , ( "no_follow" , Boolean False )
                        , ( "is_crosspostable" , Boolean False )
                        , ( "pinned" , Boolean False )
                        , ( "over_18" , Boolean False )
                        , ( "all_awardings" , Array [] )
                        , ( "awarders" , Array [] )
                        , ( "media_only" , Boolean False )
                        , ( "can_gild" , Boolean False )
                        , ( "spoiler" , Boolean False )
                        , ( "locked" , Boolean False )
                        , ( "author_flair_text" , Null )
                        , ( "treatment_tags" , Array [] )
                        , ( "visited" , Boolean False )
                        , ( "removed_by" , Null )
                        , ( "num_reports" , Null )
                        , ( "distinguished" , Null )
                        , ( "subreddit_id" , String "t5_2qh36" )
                        , ( "mod_reason_by" , Null )
                        , ( "removal_reason" , Null )
                        , ( "link_flair_background_color" , String "" )
                        , ( "id" , String "gn2tqs" )
                        , ( "is_robot_indexable" , Boolean True )
                        , ( "report_reasons" , Null )
                        , ( "author" , String "iedoub" )
                        , ( "discussion_type" , Null )
                        , ( "num_comments" , Number (5 % 1) )
                        , ( "send_replies" , Boolean True )
                        , ( "whitelist_status" , String "all_ads" )
                        , ( "contest_mode" , Boolean False )
                        , ( "mod_reports" , Array [] )
                        , ( "author_patreon_flair" , Boolean False )
                        , ( "author_flair_text_color" , Null )
                        , ( "permalink"
                          , String
                              "/r/haskell/comments/gn2tqs/alejandro_serrano_mena_on_why_functors_and/"
                          )
                        , ( "parent_whitelist_status" , String "all_ads" )
                        , ( "stickied" , Boolean False )
                        , ( "url"
                          , String
                              "https://www.youtube.com/watch?v=eZ9FpG8May8&amp;feature=youtu.be"
                          )
                        , ( "subreddit_subscribers" , Number (55194 % 1) )
                        , ( "created_utc" , Number (1589941372 % 1) )
                        , ( "num_crossposts" , Number (0 % 1) )
                        , ( "media"
                          , Object
                              [ ( "type" , String "youtube.com" )
                              , ( "oembed"
                                , Object
                                    [ ( "provider_url" , String "https://www.youtube.com/" )
                                    , ( "version" , String "1.0" )
                                    , ( "title"
                                      , String
                                          "Alejandro Serrano Mena on Why Functors and Applicatives Compose but Monads Don't"
                                      )
                                    , ( "type" , String "video" )
                                    , ( "thumbnail_width" , Number (480 % 1) )
                                    , ( "height" , Number (338 % 1) )
                                    , ( "width" , Number (600 % 1) )
                                    , ( "html"
                                      , String
                                          "&lt;iframe width=\\\"600\\\" height=\\\"338\\\" src=\\\"https://www.youtube.com/embed/eZ9FpG8May8?feature=oembed&amp;enablejsapi=1\\\" frameborder=\\\"0\\\" allow=\\\"accelerometer; autoplay; encrypted-media; gyroscope; picture-in-picture\\\" allowfullscreen&gt;&lt;/iframe&gt;"
                                      )
                                    , ( "author_name"
                                      , String "Berlin Functional Programming Group"
                                      )
                                    , ( "provider_name" , String "YouTube" )
                                    , ( "thumbnail_url"
                                      , String "https://i.ytimg.com/vi/eZ9FpG8May8/hqdefault.jpg"
                                      )
                                    , ( "thumbnail_height" , Number (360 % 1) )
                                    , ( "author_url"
                                      , String
                                          "https://www.youtube.com/channel/UCNp-DVb8cQRIOo32sZhWgNg"
                                      )
                                    ]
                                )
                              ]
                          )
                        , ( "is_video" , Boolean False )
                        ]
                    )
                  ]
              , Object
                  [ ( "kind" , String "t3" )
                  , ( "data"
                    , Object
                        [ ( "approved_at_utc" , Null )
                        , ( "subreddit" , String "haskell" )
                        , ( "selftext"
                          , String
                              "Saw a thread asking what Haskell is good for. I'm wondering now if it would be more interesting to hear what Haskell isn't good for.\\n\\nBy \\\"bad for\\\" I mean practically speaking given the current availability of ecosystem: libraries, tools, compiler extensions, devs, etc, etc. And, of course, if Haskell isn't good for something theoretically then it won't be good for it practically, so that's interesting too"
                          )
                        , ( "author_fullname" , String "t2_f4gx2" )
                        , ( "saved" , Boolean False )
                        , ( "mod_reason_title" , Null )
                        , ( "gilded" , Number (0 % 1) )
                        , ( "clicked" , Boolean False )
                        , ( "title" , String "What is Haskell bad for?" )
                        , ( "link_flair_richtext" , Array [] )
                        , ( "subreddit_name_prefixed" , String "r/haskell" )
                        , ( "hidden" , Boolean False )
                        , ( "pwls" , Number (6 % 1) )
                        , ( "link_flair_css_class" , Null )
                        , ( "downs" , Number (0 % 1) )
                        , ( "hide_score" , Boolean False )
                        , ( "name" , String "t3_gmxsp4" )
                        , ( "quarantine" , Boolean False )
                        , ( "link_flair_text_color" , String "dark" )
                        , ( "upvote_ratio" , Number (2116691824864133 % 2251799813685248) )
                        , ( "author_flair_background_color" , Null )
                        , ( "subreddit_type" , String "public" )
                        , ( "ups" , Number (26 % 1) )
                        , ( "total_awards_received" , Number (0 % 1) )
                        , ( "media_embed" , Object [] )
                        , ( "author_flair_template_id" , Null )
                        , ( "is_original_content" , Boolean False )
                        , ( "user_reports" , Array [] )
                        , ( "secure_media" , Null )
                        , ( "is_reddit_media_domain" , Boolean False )
                        , ( "is_meta" , Boolean False )
                        , ( "category" , Null )
                        , ( "secure_media_embed" , Object [] )
                        , ( "link_flair_text" , Null )
                        , ( "can_mod_post" , Boolean False )
                        , ( "score" , Number (26 % 1) )
                        , ( "approved_by" , Null )
                        , ( "author_premium" , Boolean False )
                        , ( "thumbnail" , String "" )
                        , ( "edited" , Boolean False )
                        , ( "author_flair_css_class" , Null )
                        , ( "author_flair_richtext" , Array [] )
                        , ( "gildings" , Object [] )
                        , ( "content_categories" , Null )
                        , ( "is_self" , Boolean True )
                        , ( "mod_note" , Null )
                        , ( "created" , Number (1589952776 % 1) )
                        , ( "link_flair_type" , String "text" )
                        , ( "wls" , Number (6 % 1) )
                        , ( "removed_by_category" , Null )
                        , ( "banned_by" , Null )
                        , ( "author_flair_type" , String "text" )
                        , ( "domain" , String "self.haskell" )
                        , ( "allow_live_comments" , Boolean False )
                        , ( "selftext_html"
                          , String
                              "&lt;!-- SC_OFF --&gt;&lt;div class=\\\"md\\\"&gt;&lt;p&gt;Saw a thread asking what Haskell is good for. I&amp;#39;m wondering now if it would be more interesting to hear what Haskell isn&amp;#39;t good for.&lt;/p&gt;\\n\\n&lt;p&gt;By &amp;quot;bad for&amp;quot; I mean practically speaking given the current availability of ecosystem: libraries, tools, compiler extensions, devs, etc, etc. And, of course, if Haskell isn&amp;#39;t good for something theoretically then it won&amp;#39;t be good for it practically, so that&amp;#39;s interesting too&lt;/p&gt;\\n&lt;/div&gt;&lt;!-- SC_ON --&gt;"
                          )
                        , ( "likes" , Null )
                        , ( "suggested_sort" , Null )
                        , ( "banned_at_utc" , Null )
                        , ( "view_count" , Null )
                        , ( "archived" , Boolean False )
                        , ( "no_follow" , Boolean False )
                        , ( "is_crosspostable" , Boolean False )
                        , ( "pinned" , Boolean False )
                        , ( "over_18" , Boolean False )
                        , ( "all_awardings" , Array [] )
                        , ( "awarders" , Array [] )
                        , ( "media_only" , Boolean False )
                        , ( "can_gild" , Boolean False )
                        , ( "spoiler" , Boolean False )
                        , ( "locked" , Boolean False )
                        , ( "author_flair_text" , Null )
                        , ( "treatment_tags" , Array [] )
                        , ( "visited" , Boolean False )
                        , ( "removed_by" , Null )
                        , ( "num_reports" , Null )
                        , ( "distinguished" , Null )
                        , ( "subreddit_id" , String "t5_2qh36" )
                        , ( "mod_reason_by" , Null )
                        , ( "removal_reason" , Null )
                        , ( "link_flair_background_color" , String "" )
                        , ( "id" , String "gmxsp4" )
                        , ( "is_robot_indexable" , Boolean True )
                        , ( "report_reasons" , Null )
                        , ( "author" , String "Dekans" )
                        , ( "discussion_type" , Null )
                        , ( "num_comments" , Number (65 % 1) )
                        , ( "send_replies" , Boolean True )
                        , ( "whitelist_status" , String "all_ads" )
                        , ( "contest_mode" , Boolean False )
                        , ( "mod_reports" , Array [] )
                        , ( "author_patreon_flair" , Boolean False )
                        , ( "author_flair_text_color" , Null )
                        , ( "permalink"
                          , String "/r/haskell/comments/gmxsp4/what_is_haskell_bad_for/"
                          )
                        , ( "parent_whitelist_status" , String "all_ads" )
                        , ( "stickied" , Boolean False )
                        , ( "url"
                          , String
                              "https://old.reddit.com/r/haskell/comments/gmxsp4/what_is_haskell_bad_for/"
                          )
                        , ( "subreddit_subscribers" , Number (55194 % 1) )
                        , ( "created_utc" , Number (1589923976 % 1) )
                        , ( "num_crossposts" , Number (0 % 1) )
                        , ( "media" , Null )
                        , ( "is_video" , Boolean False )
                        ]
                    )
                  ]
              , Object
                  [ ( "kind" , String "t3" )
                  , ( "data"
                    , Object
                        [ ( "approved_at_utc" , Null )
                        , ( "subreddit" , String "haskell" )
                        , ( "selftext" , String "" )
                        , ( "author_fullname" , String "t2_jxviuup" )
                        , ( "saved" , Boolean False )
                        , ( "mod_reason_title" , Null )
                        , ( "gilded" , Number (0 % 1) )
                        , ( "clicked" , Boolean False )
                        , ( "title"
                          , String
                              "Benjamin Pierce: Backtracking Generators for Random Testing"
                          )
                        , ( "link_flair_richtext" , Array [] )
                        , ( "subreddit_name_prefixed" , String "r/haskell" )
                        , ( "hidden" , Boolean False )
                        , ( "pwls" , Number (6 % 1) )
                        , ( "link_flair_css_class" , Null )
                        , ( "downs" , Number (0 % 1) )
                        , ( "hide_score" , Boolean False )
                        , ( "name" , String "t3_gmlw3d" )
                        , ( "quarantine" , Boolean False )
                        , ( "link_flair_text_color" , String "dark" )
                        , ( "upvote_ratio" , Number (2116691824864133 % 2251799813685248) )
                        , ( "author_flair_background_color" , Null )
                        , ( "subreddit_type" , String "public" )
                        , ( "ups" , Number (61 % 1) )
                        , ( "total_awards_received" , Number (0 % 1) )
                        , ( "media_embed" , Object [] )
                        , ( "author_flair_template_id" , Null )
                        , ( "is_original_content" , Boolean False )
                        , ( "user_reports" , Array [] )
                        , ( "secure_media" , Null )
                        , ( "is_reddit_media_domain" , Boolean False )
                        , ( "is_meta" , Boolean False )
                        , ( "category" , Null )
                        , ( "secure_media_embed" , Object [] )
                        , ( "link_flair_text" , Null )
                        , ( "can_mod_post" , Boolean False )
                        , ( "score" , Number (61 % 1) )
                        , ( "approved_by" , Null )
                        , ( "author_premium" , Boolean False )
                        , ( "thumbnail" , String "" )
                        , ( "edited" , Boolean False )
                        , ( "author_flair_css_class" , Null )
                        , ( "author_flair_richtext" , Array [] )
                        , ( "gildings" , Object [] )
                        , ( "content_categories" , Null )
                        , ( "is_self" , Boolean False )
                        , ( "mod_note" , Null )
                        , ( "created" , Number (1589912401 % 1) )
                        , ( "link_flair_type" , String "text" )
                        , ( "wls" , Number (6 % 1) )
                        , ( "removed_by_category" , Null )
                        , ( "banned_by" , Null )
                        , ( "author_flair_type" , String "text" )
                        , ( "domain" , String "youtube.com" )
                        , ( "allow_live_comments" , Boolean False )
                        , ( "selftext_html" , Null )
                        , ( "likes" , Null )
                        , ( "suggested_sort" , Null )
                        , ( "banned_at_utc" , Null )
                        , ( "view_count" , Null )
                        , ( "archived" , Boolean False )
                        , ( "no_follow" , Boolean False )
                        , ( "is_crosspostable" , Boolean False )
                        , ( "pinned" , Boolean False )
                        , ( "over_18" , Boolean False )
                        , ( "all_awardings" , Array [] )
                        , ( "awarders" , Array [] )
                        , ( "media_only" , Boolean False )
                        , ( "can_gild" , Boolean False )
                        , ( "spoiler" , Boolean False )
                        , ( "locked" , Boolean False )
                        , ( "author_flair_text" , Null )
                        , ( "treatment_tags" , Array [] )
                        , ( "visited" , Boolean False )
                        , ( "removed_by" , Null )
                        , ( "num_reports" , Null )
                        , ( "distinguished" , Null )
                        , ( "subreddit_id" , String "t5_2qh36" )
                        , ( "mod_reason_by" , Null )
                        , ( "removal_reason" , Null )
                        , ( "link_flair_background_color" , String "" )
                        , ( "id" , String "gmlw3d" )
                        , ( "is_robot_indexable" , Boolean True )
                        , ( "report_reasons" , Null )
                        , ( "author" , String "iedoub" )
                        , ( "discussion_type" , Null )
                        , ( "num_comments" , Number (2 % 1) )
                        , ( "send_replies" , Boolean True )
                        , ( "whitelist_status" , String "all_ads" )
                        , ( "contest_mode" , Boolean False )
                        , ( "mod_reports" , Array [] )
                        , ( "author_patreon_flair" , Boolean False )
                        , ( "author_flair_text_color" , Null )
                        , ( "permalink"
                          , String
                              "/r/haskell/comments/gmlw3d/benjamin_pierce_backtracking_generators_for/"
                          )
                        , ( "parent_whitelist_status" , String "all_ads" )
                        , ( "stickied" , Boolean False )
                        , ( "url"
                          , String
                              "https://www.youtube.com/watch?v=dfZ94N0hS4I&amp;feature=youtu.be"
                          )
                        , ( "subreddit_subscribers" , Number (55194 % 1) )
                        , ( "created_utc" , Number (1589883601 % 1) )
                        , ( "num_crossposts" , Number (0 % 1) )
                        , ( "media" , Null )
                        , ( "is_video" , Boolean False )
                        ]
                    )
                  ]
              , Object
                  [ ( "kind" , String "t3" )
                  , ( "data"
                    , Object
                        [ ( "approved_at_utc" , Null )
                        , ( "subreddit" , String "haskell" )
                        , ( "selftext" , String "" )
                        , ( "author_fullname" , String "t2_2zl2" )
                        , ( "saved" , Boolean False )
                        , ( "mod_reason_title" , Null )
                        , ( "gilded" , Number (0 % 1) )
                        , ( "clicked" , Boolean False )
                        , ( "title"
                          , String
                              "Haskenthetical - another take on \\\"Haskell with a Lisp syntax\\\""
                          )
                        , ( "link_flair_richtext" , Array [] )
                        , ( "subreddit_name_prefixed" , String "r/haskell" )
                        , ( "hidden" , Boolean False )
                        , ( "pwls" , Number (6 % 1) )
                        , ( "link_flair_css_class" , Null )
                        , ( "downs" , Number (0 % 1) )
                        , ( "hide_score" , Boolean False )
                        , ( "name" , String "t3_gmybcf" )
                        , ( "quarantine" , Boolean False )
                        , ( "link_flair_text_color" , String "dark" )
                        , ( "upvote_ratio" , Number (1 % 1) )
                        , ( "author_flair_background_color" , Null )
                        , ( "subreddit_type" , String "public" )
                        , ( "ups" , Number (5 % 1) )
                        , ( "total_awards_received" , Number (0 % 1) )
                        , ( "media_embed" , Object [] )
                        , ( "author_flair_template_id" , Null )
                        , ( "is_original_content" , Boolean False )
                        , ( "user_reports" , Array [] )
                        , ( "secure_media" , Null )
                        , ( "is_reddit_media_domain" , Boolean False )
                        , ( "is_meta" , Boolean False )
                        , ( "category" , Null )
                        , ( "secure_media_embed" , Object [] )
                        , ( "link_flair_text" , Null )
                        , ( "can_mod_post" , Boolean False )
                        , ( "score" , Number (5 % 1) )
                        , ( "approved_by" , Null )
                        , ( "author_premium" , Boolean False )
                        , ( "thumbnail" , String "" )
                        , ( "edited" , Boolean False )
                        , ( "author_flair_css_class" , Null )
                        , ( "author_flair_richtext" , Array [] )
                        , ( "gildings" , Object [] )
                        , ( "content_categories" , Null )
                        , ( "is_self" , Boolean False )
                        , ( "mod_note" , Null )
                        , ( "created" , Number (1589954453 % 1) )
                        , ( "link_flair_type" , String "text" )
                        , ( "wls" , Number (6 % 1) )
                        , ( "removed_by_category" , Null )
                        , ( "banned_by" , Null )
                        , ( "author_flair_type" , String "text" )
                        , ( "domain" , String "reasonableapproximation.net" )
                        , ( "allow_live_comments" , Boolean False )
                        , ( "selftext_html" , Null )
                        , ( "likes" , Null )
                        , ( "suggested_sort" , Null )
                        , ( "banned_at_utc" , Null )
                        , ( "view_count" , Null )
                        , ( "archived" , Boolean False )
                        , ( "no_follow" , Boolean False )
                        , ( "is_crosspostable" , Boolean False )
                        , ( "pinned" , Boolean False )
                        , ( "over_18" , Boolean False )
                        , ( "all_awardings" , Array [] )
                        , ( "awarders" , Array [] )
                        , ( "media_only" , Boolean False )
                        , ( "can_gild" , Boolean False )
                        , ( "spoiler" , Boolean False )
                        , ( "locked" , Boolean False )
                        , ( "author_flair_text" , Null )
                        , ( "treatment_tags" , Array [] )
                        , ( "visited" , Boolean False )
                        , ( "removed_by" , Null )
                        , ( "num_reports" , Null )
                        , ( "distinguished" , Null )
                        , ( "subreddit_id" , String "t5_2qh36" )
                        , ( "mod_reason_by" , Null )
                        , ( "removal_reason" , Null )
                        , ( "link_flair_background_color" , String "" )
                        , ( "id" , String "gmybcf" )
                        , ( "is_robot_indexable" , Boolean True )
                        , ( "report_reasons" , Null )
                        , ( "author" , String "philh" )
                        , ( "discussion_type" , Null )
                        , ( "num_comments" , Number (2 % 1) )
                        , ( "send_replies" , Boolean True )
                        , ( "whitelist_status" , String "all_ads" )
                        , ( "contest_mode" , Boolean False )
                        , ( "mod_reports" , Array [] )
                        , ( "author_patreon_flair" , Boolean False )
                        , ( "author_flair_text_color" , Null )
                        , ( "permalink"
                          , String
                              "/r/haskell/comments/gmybcf/haskenthetical_another_take_on_haskell_with_a/"
                          )
                        , ( "parent_whitelist_status" , String "all_ads" )
                        , ( "stickied" , Boolean False )
                        , ( "url"
                          , String
                              "http://reasonableapproximation.net/2020/05/19/haskenthetical.html"
                          )
                        , ( "subreddit_subscribers" , Number (55194 % 1) )
                        , ( "created_utc" , Number (1589925653 % 1) )
                        , ( "num_crossposts" , Number (0 % 1) )
                        , ( "media" , Null )
                        , ( "is_video" , Boolean False )
                        ]
                    )
                  ]
              , Object
                  [ ( "kind" , String "t3" )
                  , ( "data"
                    , Object
                        [ ( "approved_at_utc" , Null )
                        , ( "subreddit" , String "haskell" )
                        , ( "selftext" , String "" )
                        , ( "author_fullname" , String "t2_4hurx" )
                        , ( "saved" , Boolean False )
                        , ( "mod_reason_title" , Null )
                        , ( "gilded" , Number (0 % 1) )
                        , ( "clicked" , Boolean False )
                        , ( "title" , String "How to define JSON instances quickly" )
                        , ( "link_flair_richtext" , Array [] )
                        , ( "subreddit_name_prefixed" , String "r/haskell" )
                        , ( "hidden" , Boolean False )
                        , ( "pwls" , Number (6 % 1) )
                        , ( "link_flair_css_class" , Null )
                        , ( "downs" , Number (0 % 1) )
                        , ( "hide_score" , Boolean False )
                        , ( "name" , String "t3_gmmp65" )
                        , ( "quarantine" , Boolean False )
                        , ( "link_flair_text_color" , String "dark" )
                        , ( "upvote_ratio" , Number (1080863910568919 % 1125899906842624) )
                        , ( "author_flair_background_color" , Null )
                        , ( "subreddit_type" , String "public" )
                        , ( "ups" , Number (24 % 1) )
                        , ( "total_awards_received" , Number (0 % 1) )
                        , ( "media_embed" , Object [] )
                        , ( "author_flair_template_id" , Null )
                        , ( "is_original_content" , Boolean False )
                        , ( "user_reports" , Array [] )
                        , ( "secure_media" , Null )
                        , ( "is_reddit_media_domain" , Boolean False )
                        , ( "is_meta" , Boolean False )
                        , ( "category" , Null )
                        , ( "secure_media_embed" , Object [] )
                        , ( "link_flair_text" , Null )
                        , ( "can_mod_post" , Boolean False )
                        , ( "score" , Number (24 % 1) )
                        , ( "approved_by" , Null )
                        , ( "author_premium" , Boolean False )
                        , ( "thumbnail" , String "" )
                        , ( "edited" , Boolean False )
                        , ( "author_flair_css_class" , Null )
                        , ( "author_flair_richtext" , Array [] )
                        , ( "gildings" , Object [] )
                        , ( "content_categories" , Null )
                        , ( "is_self" , Boolean False )
                        , ( "mod_note" , Null )
                        , ( "created" , Number (1589916349 % 1) )
                        , ( "link_flair_type" , String "text" )
                        , ( "wls" , Number (6 % 1) )
                        , ( "removed_by_category" , Null )
                        , ( "banned_by" , Null )
                        , ( "author_flair_type" , String "text" )
                        , ( "domain" , String "dev.to" )
                        , ( "allow_live_comments" , Boolean False )
                        , ( "selftext_html" , Null )
                        , ( "likes" , Null )
                        , ( "suggested_sort" , Null )
                        , ( "banned_at_utc" , Null )
                        , ( "view_count" , Null )
                        , ( "archived" , Boolean False )
                        , ( "no_follow" , Boolean False )
                        , ( "is_crosspostable" , Boolean False )
                        , ( "pinned" , Boolean False )
                        , ( "over_18" , Boolean False )
                        , ( "all_awardings" , Array [] )
                        , ( "awarders" , Array [] )
                        , ( "media_only" , Boolean False )
                        , ( "can_gild" , Boolean False )
                        , ( "spoiler" , Boolean False )
                        , ( "locked" , Boolean False )
                        , ( "author_flair_text" , Null )
                        , ( "treatment_tags" , Array [] )
                        , ( "visited" , Boolean False )
                        , ( "removed_by" , Null )
                        , ( "num_reports" , Null )
                        , ( "distinguished" , Null )
                        , ( "subreddit_id" , String "t5_2qh36" )
                        , ( "mod_reason_by" , Null )
                        , ( "removal_reason" , Null )
                        , ( "link_flair_background_color" , String "" )
                        , ( "id" , String "gmmp65" )
                        , ( "is_robot_indexable" , Boolean True )
                        , ( "report_reasons" , Null )
                        , ( "author" , String "taylorfausak" )
                        , ( "discussion_type" , Null )
                        , ( "num_comments" , Number (9 % 1) )
                        , ( "send_replies" , Boolean True )
                        , ( "whitelist_status" , String "all_ads" )
                        , ( "contest_mode" , Boolean False )
                        , ( "mod_reports" , Array [] )
                        , ( "author_patreon_flair" , Boolean False )
                        , ( "author_flair_text_color" , Null )
                        , ( "permalink"
                          , String
                              "/r/haskell/comments/gmmp65/how_to_define_json_instances_quickly/"
                          )
                        , ( "parent_whitelist_status" , String "all_ads" )
                        , ( "stickied" , Boolean False )
                        , ( "url"
                          , String
                              "https://dev.to/tfausak/how-to-define-json-instances-quickly-5ei7"
                          )
                        , ( "subreddit_subscribers" , Number (55194 % 1) )
                        , ( "created_utc" , Number (1589887549 % 1) )
                        , ( "num_crossposts" , Number (0 % 1) )
                        , ( "media" , Null )
                        , ( "is_video" , Boolean False )
                        ]
                    )
                  ]
              , Object
                  [ ( "kind" , String "t3" )
                  , ( "data"
                    , Object
                        [ ( "approved_at_utc" , Null )
                        , ( "subreddit" , String "haskell" )
                        , ( "selftext"
                          , String
                              "I try to manage my packages by nix, but the following command `nix-env -iA nixpkgs.stack` do not create a `.stack` folder for me, and then run stack global will throw exception like this.\\n\\n```shell\\n$ stack ghci  \\nopenAnonymousTempFileFromDir: inappropriate type (Is a directory)\\n```"
                          )
                        , ( "author_fullname" , String "t2_22yozddx" )
                        , ( "saved" , Boolean False )
                        , ( "mod_reason_title" , Null )
                        , ( "gilded" , Number (0 % 1) )
                        , ( "clicked" , Boolean False )
                        , ( "title"
                          , String
                              "Stack installed by nix seems do not create `.stack` folder under home dir properly."
                          )
                        , ( "link_flair_richtext" , Array [] )
                        , ( "subreddit_name_prefixed" , String "r/haskell" )
                        , ( "hidden" , Boolean False )
                        , ( "pwls" , Number (6 % 1) )
                        , ( "link_flair_css_class" , Null )
                        , ( "downs" , Number (0 % 1) )
                        , ( "hide_score" , Boolean False )
                        , ( "name" , String "t3_gn3vhr" )
                        , ( "quarantine" , Boolean False )
                        , ( "link_flair_text_color" , String "dark" )
                        , ( "upvote_ratio" , Number (1 % 2) )
                        , ( "author_flair_background_color" , Null )
                        , ( "subreddit_type" , String "public" )
                        , ( "ups" , Number (0 % 1) )
                        , ( "total_awards_received" , Number (0 % 1) )
                        , ( "media_embed" , Object [] )
                        , ( "author_flair_template_id" , Null )
                        , ( "is_original_content" , Boolean False )
                        , ( "user_reports" , Array [] )
                        , ( "secure_media" , Null )
                        , ( "is_reddit_media_domain" , Boolean False )
                        , ( "is_meta" , Boolean False )
                        , ( "category" , Null )
                        , ( "secure_media_embed" , Object [] )
                        , ( "link_flair_text" , Null )
                        , ( "can_mod_post" , Boolean False )
                        , ( "score" , Number (0 % 1) )
                        , ( "approved_by" , Null )
                        , ( "author_premium" , Boolean False )
                        , ( "thumbnail" , String "" )
                        , ( "edited" , Boolean False )
                        , ( "author_flair_css_class" , Null )
                        , ( "author_flair_richtext" , Array [] )
                        , ( "gildings" , Object [] )
                        , ( "content_categories" , Null )
                        , ( "is_self" , Boolean True )
                        , ( "mod_note" , Null )
                        , ( "created" , Number (1589974381 % 1) )
                        , ( "link_flair_type" , String "text" )
                        , ( "wls" , Number (6 % 1) )
                        , ( "removed_by_category" , Null )
                        , ( "banned_by" , Null )
                        , ( "author_flair_type" , String "text" )
                        , ( "domain" , String "self.haskell" )
                        , ( "allow_live_comments" , Boolean False )
                        , ( "selftext_html"
                          , String
                              "&lt;!-- SC_OFF --&gt;&lt;div class=\\\"md\\\"&gt;&lt;p&gt;I try to manage my packages by nix, but the following command &lt;code&gt;nix-env -iA nixpkgs.stack&lt;/code&gt; do not create a &lt;code&gt;.stack&lt;/code&gt; folder for me, and then run stack global will throw exception like this.&lt;/p&gt;\\n\\n&lt;p&gt;&lt;code&gt;shell\\n$ stack ghci  \\nopenAnonymousTempFileFromDir: inappropriate type (Is a directory)\\n&lt;/code&gt;&lt;/p&gt;\\n&lt;/div&gt;&lt;!-- SC_ON --&gt;"
                          )
                        , ( "likes" , Null )
                        , ( "suggested_sort" , Null )
                        , ( "banned_at_utc" , Null )
                        , ( "view_count" , Null )
                        , ( "archived" , Boolean False )
                        , ( "no_follow" , Boolean True )
                        , ( "is_crosspostable" , Boolean False )
                        , ( "pinned" , Boolean False )
                        , ( "over_18" , Boolean False )
                        , ( "all_awardings" , Array [] )
                        , ( "awarders" , Array [] )
                        , ( "media_only" , Boolean False )
                        , ( "can_gild" , Boolean False )
                        , ( "spoiler" , Boolean False )
                        , ( "locked" , Boolean False )
                        , ( "author_flair_text" , Null )
                        , ( "treatment_tags" , Array [] )
                        , ( "visited" , Boolean False )
                        , ( "removed_by" , Null )
                        , ( "num_reports" , Null )
                        , ( "distinguished" , Null )
                        , ( "subreddit_id" , String "t5_2qh36" )
                        , ( "mod_reason_by" , Null )
                        , ( "removal_reason" , Null )
                        , ( "link_flair_background_color" , String "" )
                        , ( "id" , String "gn3vhr" )
                        , ( "is_robot_indexable" , Boolean True )
                        , ( "report_reasons" , Null )
                        , ( "author" , String "wangqiao11" )
                        , ( "discussion_type" , Null )
                        , ( "num_comments" , Number (3 % 1) )
                        , ( "send_replies" , Boolean True )
                        , ( "whitelist_status" , String "all_ads" )
                        , ( "contest_mode" , Boolean False )
                        , ( "mod_reports" , Array [] )
                        , ( "author_patreon_flair" , Boolean False )
                        , ( "author_flair_text_color" , Null )
                        , ( "permalink"
                          , String
                              "/r/haskell/comments/gn3vhr/stack_installed_by_nix_seems_do_not_create_stack/"
                          )
                        , ( "parent_whitelist_status" , String "all_ads" )
                        , ( "stickied" , Boolean False )
                        , ( "url"
                          , String
                              "https://old.reddit.com/r/haskell/comments/gn3vhr/stack_installed_by_nix_seems_do_not_create_stack/"
                          )
                        , ( "subreddit_subscribers" , Number (55194 % 1) )
                        , ( "created_utc" , Number (1589945581 % 1) )
                        , ( "num_crossposts" , Number (0 % 1) )
                        , ( "media" , Null )
                        , ( "is_video" , Boolean False )
                        ]
                    )
                  ]
              , Object
                  [ ( "kind" , String "t3" )
                  , ( "data"
                    , Object
                        [ ( "approved_at_utc" , Null )
                        , ( "subreddit" , String "haskell" )
                        , ( "selftext"
                          , String
                              "I've been beating my head against this issue for a while and thought maybe someone here has a good idea of how to approach this problem.   \\nI'm working on a program which has a simple terminal GUI interface using [brick](https://github.com/jtdaugherty/brick), and now I want to be able to run SMT queries in the program using the [SBV](https://hackage.haskell.org/package/sbv-8.6) library. The problem is that the interaction between the program and the SMT solver is being tracked in a monad context (\\\\`[MonadQuery](https://hackage.haskell.org/package/sbv-8.6/docs/src/Data.SBV.Core.Symbolic.html#MonadQuery)\\\\`, \\\\`Query a\\\\` or \\\\`Symbolic a\\\\`), while the event handling monad \\\\`[EventM n a](https://github.com/jtdaugherty/brick/blob/758d8138301ce521214247bd9190abbff7ec0f3d/src/Brick/Types.hs#L128)\\\\` of brick seems to only allow IO actions.  \\n\\n\\nHow would I best go about unifying these contexts? Is there a way to generalize the event handling of brick to allow for other types of monadic actions to be performed? Or should I rather try to save the state that defines the \\\\`MonadQuery\\\\` of SBV in the application state? I found no good way of \\\"saving\\\" the context of a MonadQuery to be able to \\\"resume\\\" it a later time."
                          )
                        , ( "author_fullname" , String "t2_cx67k" )
                        , ( "saved" , Boolean False )
                        , ( "mod_reason_title" , Null )
                        , ( "gilded" , Number (0 % 1) )
                        , ( "clicked" , Boolean False )
                        , ( "title" , String "Combining Brick and SBV monadic contexts" )
                        , ( "link_flair_richtext" , Array [] )
                        , ( "subreddit_name_prefixed" , String "r/haskell" )
                        , ( "hidden" , Boolean False )
                        , ( "pwls" , Number (6 % 1) )
                        , ( "link_flair_css_class" , Null )
                        , ( "downs" , Number (0 % 1) )
                        , ( "hide_score" , Boolean False )
                        , ( "name" , String "t3_gmn78x" )
                        , ( "quarantine" , Boolean False )
                        , ( "link_flair_text_color" , String "dark" )
                        , ( "upvote_ratio" , Number (1 % 1) )
                        , ( "author_flair_background_color" , Null )
                        , ( "subreddit_type" , String "public" )
                        , ( "ups" , Number (9 % 1) )
                        , ( "total_awards_received" , Number (0 % 1) )
                        , ( "media_embed" , Object [] )
                        , ( "author_flair_template_id" , Null )
                        , ( "is_original_content" , Boolean False )
                        , ( "user_reports" , Array [] )
                        , ( "secure_media" , Null )
                        , ( "is_reddit_media_domain" , Boolean False )
                        , ( "is_meta" , Boolean False )
                        , ( "category" , Null )
                        , ( "secure_media_embed" , Object [] )
                        , ( "link_flair_text" , Null )
                        , ( "can_mod_post" , Boolean False )
                        , ( "score" , Number (9 % 1) )
                        , ( "approved_by" , Null )
                        , ( "author_premium" , Boolean False )
                        , ( "thumbnail" , String "" )
                        , ( "edited" , Boolean False )
                        , ( "author_flair_css_class" , Null )
                        , ( "author_flair_richtext" , Array [] )
                        , ( "gildings" , Object [] )
                        , ( "content_categories" , Null )
                        , ( "is_self" , Boolean True )
                        , ( "mod_note" , Null )
                        , ( "created" , Number (1589918474 % 1) )
                        , ( "link_flair_type" , String "text" )
                        , ( "wls" , Number (6 % 1) )
                        , ( "removed_by_category" , Null )
                        , ( "banned_by" , Null )
                        , ( "author_flair_type" , String "text" )
                        , ( "domain" , String "self.haskell" )
                        , ( "allow_live_comments" , Boolean False )
                        , ( "selftext_html"
                          , String
                              "&lt;!-- SC_OFF --&gt;&lt;div class=\\\"md\\\"&gt;&lt;p&gt;I&amp;#39;ve been beating my head against this issue for a while and thought maybe someone here has a good idea of how to approach this problem.&lt;br/&gt;\\nI&amp;#39;m working on a program which has a simple terminal GUI interface using &lt;a href=\\\"https://github.com/jtdaugherty/brick\\\"&gt;brick&lt;/a&gt;, and now I want to be able to run SMT queries in the program using the &lt;a href=\\\"https://hackage.haskell.org/package/sbv-8.6\\\"&gt;SBV&lt;/a&gt; library. The problem is that the interaction between the program and the SMT solver is being tracked in a monad context (`&lt;a href=\\\"https://hackage.haskell.org/package/sbv-8.6/docs/src/Data.SBV.Core.Symbolic.html#MonadQuery\\\"&gt;MonadQuery&lt;/a&gt;`, `Query a` or `Symbolic a`), while the event handling monad `&lt;a href=\\\"https://github.com/jtdaugherty/brick/blob/758d8138301ce521214247bd9190abbff7ec0f3d/src/Brick/Types.hs#L128\\\"&gt;EventM n a&lt;/a&gt;` of brick seems to only allow IO actions.  &lt;/p&gt;\\n\\n&lt;p&gt;How would I best go about unifying these contexts? Is there a way to generalize the event handling of brick to allow for other types of monadic actions to be performed? Or should I rather try to save the state that defines the `MonadQuery` of SBV in the application state? I found no good way of &amp;quot;saving&amp;quot; the context of a MonadQuery to be able to &amp;quot;resume&amp;quot; it a later time.&lt;/p&gt;\\n&lt;/div&gt;&lt;!-- SC_ON --&gt;"
                          )
                        , ( "likes" , Null )
                        , ( "suggested_sort" , Null )
                        , ( "banned_at_utc" , Null )
                        , ( "view_count" , Null )
                        , ( "archived" , Boolean False )
                        , ( "no_follow" , Boolean False )
                        , ( "is_crosspostable" , Boolean False )
                        , ( "pinned" , Boolean False )
                        , ( "over_18" , Boolean False )
                        , ( "all_awardings" , Array [] )
                        , ( "awarders" , Array [] )
                        , ( "media_only" , Boolean False )
                        , ( "can_gild" , Boolean False )
                        , ( "spoiler" , Boolean False )
                        , ( "locked" , Boolean False )
                        , ( "author_flair_text" , Null )
                        , ( "treatment_tags" , Array [] )
                        , ( "visited" , Boolean False )
                        , ( "removed_by" , Null )
                        , ( "num_reports" , Null )
                        , ( "distinguished" , Null )
                        , ( "subreddit_id" , String "t5_2qh36" )
                        , ( "mod_reason_by" , Null )
                        , ( "removal_reason" , Null )
                        , ( "link_flair_background_color" , String "" )
                        , ( "id" , String "gmn78x" )
                        , ( "is_robot_indexable" , Boolean True )
                        , ( "report_reasons" , Null )
                        , ( "author" , String "Scentable" )
                        , ( "discussion_type" , Null )
                        , ( "num_comments" , Number (5 % 1) )
                        , ( "send_replies" , Boolean True )
                        , ( "whitelist_status" , String "all_ads" )
                        , ( "contest_mode" , Boolean False )
                        , ( "mod_reports" , Array [] )
                        , ( "author_patreon_flair" , Boolean False )
                        , ( "author_flair_text_color" , Null )
                        , ( "permalink"
                          , String
                              "/r/haskell/comments/gmn78x/combining_brick_and_sbv_monadic_contexts/"
                          )
                        , ( "parent_whitelist_status" , String "all_ads" )
                        , ( "stickied" , Boolean False )
                        , ( "url"
                          , String
                              "https://old.reddit.com/r/haskell/comments/gmn78x/combining_brick_and_sbv_monadic_contexts/"
                          )
                        , ( "subreddit_subscribers" , Number (55194 % 1) )
                        , ( "created_utc" , Number (1589889674 % 1) )
                        , ( "num_crossposts" , Number (0 % 1) )
                        , ( "media" , Null )
                        , ( "is_video" , Boolean False )
                        ]
                    )
                  ]
              , Object
                  [ ( "kind" , String "t3" )
                  , ( "data"
                    , Object
                        [ ( "approved_at_utc" , Null )
                        , ( "subreddit" , String "haskell" )
                        , ( "selftext" , String "" )
                        , ( "author_fullname" , String "t2_fr9sxjo" )
                        , ( "saved" , Boolean False )
                        , ( "mod_reason_title" , Null )
                        , ( "gilded" , Number (0 % 1) )
                        , ( "clicked" , Boolean False )
                        , ( "title"
                          , String "I am having difficulty installing Haskero for VSCode"
                          )
                        , ( "link_flair_richtext" , Array [] )
                        , ( "subreddit_name_prefixed" , String "r/haskell" )
                        , ( "hidden" , Boolean False )
                        , ( "pwls" , Number (6 % 1) )
                        , ( "link_flair_css_class" , Null )
                        , ( "downs" , Number (0 % 1) )
                        , ( "hide_score" , Boolean False )
                        , ( "name" , String "t3_gmte13" )
                        , ( "quarantine" , Boolean False )
                        , ( "link_flair_text_color" , String "dark" )
                        , ( "upvote_ratio" , Number (3 % 4) )
                        , ( "author_flair_background_color" , Null )
                        , ( "subreddit_type" , String "public" )
                        , ( "ups" , Number (4 % 1) )
                        , ( "total_awards_received" , Number (0 % 1) )
                        , ( "media_embed" , Object [] )
                        , ( "author_flair_template_id" , Null )
                        , ( "is_original_content" , Boolean False )
                        , ( "user_reports" , Array [] )
                        , ( "secure_media" , Null )
                        , ( "is_reddit_media_domain" , Boolean False )
                        , ( "is_meta" , Boolean False )
                        , ( "category" , Null )
                        , ( "secure_media_embed" , Object [] )
                        , ( "link_flair_text" , Null )
                        , ( "can_mod_post" , Boolean False )
                        , ( "score" , Number (4 % 1) )
                        , ( "approved_by" , Null )
                        , ( "author_premium" , Boolean False )
                        , ( "thumbnail" , String "" )
                        , ( "edited" , Boolean False )
                        , ( "author_flair_css_class" , Null )
                        , ( "author_flair_richtext" , Array [] )
                        , ( "gildings" , Object [] )
                        , ( "content_categories" , Null )
                        , ( "is_self" , Boolean False )
                        , ( "mod_note" , Null )
                        , ( "crosspost_parent_list"
                          , Array
                              [ Object
                                  [ ( "approved_at_utc" , Null )
                                  , ( "subreddit" , String "vscode" )
                                  , ( "selftext"
                                    , String
                                        "I am currently trying to install Haskero for VSCode. I am using [this link](https://gitlab.com/vannnns/haskero/blob/master/client/doc/installation.md) and following the instructions, however I am stuck on step 5. Whenever I type\\n\\n    stack build intero --copy-compiler-tool\\n\\ninto the terminal, I get this error message:\\n\\n    Error: While constructing the build plan, the following exceptions were encountered:\\n    \\n    In the dependencies for intero-0.1.40:\\n        ghc-8.8.3 from stack configuration does not match &gt;=7.8 &amp;&amp; &lt;=8.6.5  (latest matching version is 8.6.5)\\n    needed since intero is a build target.\\n    \\n    Some different approaches to resolving this:\\n    \\n      * Set 'allow-newer: true' in C:\\\\sr\\\\config.yaml to ignore all version constraints and build anyway.\\n    \\n      * Recommended action: try adding the following to your extra-deps in C:\\\\sr\\\\global-project\\\\stack.yaml:\\n    \\n    - ghc-8.6.5@sha256:3591225289bdf8cf8f62b10f2aebc9ea3e25a15294545a5312a419e0317784f9,13976\\n    \\n    Plan construction failed.\\n\\nI do not know how to handle this. Any  suggestions? Thank you in advance."
                                    )
                                  , ( "author_fullname" , String "t2_fr9sxjo" )
                                  , ( "saved" , Boolean False )
                                  , ( "mod_reason_title" , Null )
                                  , ( "gilded" , Number (0 % 1) )
                                  , ( "clicked" , Boolean False )
                                  , ( "title"
                                    , String "I am having difficulty installing Haskero."
                                    )
                                  , ( "link_flair_richtext" , Array [] )
                                  , ( "subreddit_name_prefixed" , String "r/vscode" )
                                  , ( "hidden" , Boolean False )
                                  , ( "pwls" , Number (6 % 1) )
                                  , ( "link_flair_css_class" , Null )
                                  , ( "downs" , Number (0 % 1) )
                                  , ( "hide_score" , Boolean False )
                                  , ( "name" , String "t3_gm53c8" )
                                  , ( "quarantine" , Boolean False )
                                  , ( "link_flair_text_color" , String "dark" )
                                  , ( "upvote_ratio"
                                    , Number (3242591731706757 % 4503599627370496)
                                    )
                                  , ( "author_flair_background_color" , Null )
                                  , ( "subreddit_type" , String "public" )
                                  , ( "ups" , Number (3 % 1) )
                                  , ( "total_awards_received" , Number (0 % 1) )
                                  , ( "media_embed" , Object [] )
                                  , ( "author_flair_template_id" , Null )
                                  , ( "is_original_content" , Boolean True )
                                  , ( "user_reports" , Array [] )
                                  , ( "secure_media" , Null )
                                  , ( "is_reddit_media_domain" , Boolean False )
                                  , ( "is_meta" , Boolean False )
                                  , ( "category" , Null )
                                  , ( "secure_media_embed" , Object [] )
                                  , ( "link_flair_text" , Null )
                                  , ( "can_mod_post" , Boolean False )
                                  , ( "score" , Number (3 % 1) )
                                  , ( "approved_by" , Null )
                                  , ( "author_premium" , Boolean False )
                                  , ( "thumbnail" , String "" )
                                  , ( "edited" , Boolean False )
                                  , ( "author_flair_css_class" , Null )
                                  , ( "author_flair_richtext" , Array [] )
                                  , ( "gildings" , Object [] )
                                  , ( "content_categories" , Null )
                                  , ( "is_self" , Boolean True )
                                  , ( "mod_note" , Null )
                                  , ( "created" , Number (1589849248 % 1) )
                                  , ( "link_flair_type" , String "text" )
                                  , ( "wls" , Number (6 % 1) )
                                  , ( "removed_by_category" , Null )
                                  , ( "banned_by" , Null )
                                  , ( "author_flair_type" , String "text" )
                                  , ( "domain" , String "self.vscode" )
                                  , ( "allow_live_comments" , Boolean False )
                                  , ( "selftext_html"
                                    , String
                                        "&lt;!-- SC_OFF --&gt;&lt;div class=\\\"md\\\"&gt;&lt;p&gt;I am currently trying to install Haskero for VSCode. I am using &lt;a href=\\\"https://gitlab.com/vannnns/haskero/blob/master/client/doc/installation.md\\\"&gt;this link&lt;/a&gt; and following the instructions, however I am stuck on step 5. Whenever I type&lt;/p&gt;\\n\\n&lt;pre&gt;&lt;code&gt;stack build intero --copy-compiler-tool\\n&lt;/code&gt;&lt;/pre&gt;\\n\\n&lt;p&gt;into the terminal, I get this error message:&lt;/p&gt;\\n\\n&lt;pre&gt;&lt;code&gt;Error: While constructing the build plan, the following exceptions were encountered:\\n\\nIn the dependencies for intero-0.1.40:\\n    ghc-8.8.3 from stack configuration does not match &amp;gt;=7.8 &amp;amp;&amp;amp; &amp;lt;=8.6.5  (latest matching version is 8.6.5)\\nneeded since intero is a build target.\\n\\nSome different approaches to resolving this:\\n\\n  * Set &amp;#39;allow-newer: true&amp;#39; in C:\\\\sr\\\\config.yaml to ignore all version constraints and build anyway.\\n\\n  * Recommended action: try adding the following to your extra-deps in C:\\\\sr\\\\global-project\\\\stack.yaml:\\n\\n- ghc-8.6.5@sha256:3591225289bdf8cf8f62b10f2aebc9ea3e25a15294545a5312a419e0317784f9,13976\\n\\nPlan construction failed.\\n&lt;/code&gt;&lt;/pre&gt;\\n\\n&lt;p&gt;I do not know how to handle this. Any  suggestions? Thank you in advance.&lt;/p&gt;\\n&lt;/div&gt;&lt;!-- SC_ON --&gt;"
                                    )
                                  , ( "likes" , Null )
                                  , ( "suggested_sort" , Null )
                                  , ( "banned_at_utc" , Null )
                                  , ( "view_count" , Null )
                                  , ( "archived" , Boolean False )
                                  , ( "no_follow" , Boolean False )
                                  , ( "is_crosspostable" , Boolean False )
                                  , ( "pinned" , Boolean False )
                                  , ( "over_18" , Boolean False )
                                  , ( "all_awardings" , Array [] )
                                  , ( "awarders" , Array [] )
                                  , ( "media_only" , Boolean False )
                                  , ( "can_gild" , Boolean False )
                                  , ( "spoiler" , Boolean False )
                                  , ( "locked" , Boolean False )
                                  , ( "author_flair_text" , Null )
                                  , ( "treatment_tags" , Array [] )
                                  , ( "visited" , Boolean False )
                                  , ( "removed_by" , Null )
                                  , ( "num_reports" , Null )
                                  , ( "distinguished" , Null )
                                  , ( "subreddit_id" , String "t5_381yu" )
                                  , ( "mod_reason_by" , Null )
                                  , ( "removal_reason" , Null )
                                  , ( "link_flair_background_color" , String "" )
                                  , ( "id" , String "gm53c8" )
                                  , ( "is_robot_indexable" , Boolean True )
                                  , ( "report_reasons" , Null )
                                  , ( "author" , String "The-CPMills" )
                                  , ( "discussion_type" , Null )
                                  , ( "num_comments" , Number (0 % 1) )
                                  , ( "send_replies" , Boolean True )
                                  , ( "whitelist_status" , String "all_ads" )
                                  , ( "contest_mode" , Boolean False )
                                  , ( "mod_reports" , Array [] )
                                  , ( "author_patreon_flair" , Boolean False )
                                  , ( "author_flair_text_color" , Null )
                                  , ( "permalink"
                                    , String
                                        "/r/vscode/comments/gm53c8/i_am_having_difficulty_installing_haskero/"
                                    )
                                  , ( "parent_whitelist_status" , String "all_ads" )
                                  , ( "stickied" , Boolean False )
                                  , ( "url"
                                    , String
                                        "https://old.reddit.com/r/vscode/comments/gm53c8/i_am_having_difficulty_installing_haskero/"
                                    )
                                  , ( "subreddit_subscribers" , Number (40653 % 1) )
                                  , ( "created_utc" , Number (1589820448 % 1) )
                                  , ( "num_crossposts" , Number (1 % 1) )
                                  , ( "media" , Null )
                                  , ( "is_video" , Boolean False )
                                  ]
                              ]
                          )
                        , ( "created" , Number (1589939114 % 1) )
                        , ( "link_flair_type" , String "text" )
                        , ( "wls" , Number (6 % 1) )
                        , ( "removed_by_category" , Null )
                        , ( "banned_by" , Null )
                        , ( "author_flair_type" , String "text" )
                        , ( "domain" , String "self.vscode" )
                        , ( "allow_live_comments" , Boolean False )
                        , ( "selftext_html" , Null )
                        , ( "likes" , Null )
                        , ( "suggested_sort" , Null )
                        , ( "banned_at_utc" , Null )
                        , ( "view_count" , Null )
                        , ( "archived" , Boolean False )
                        , ( "no_follow" , Boolean True )
                        , ( "is_crosspostable" , Boolean False )
                        , ( "pinned" , Boolean False )
                        , ( "over_18" , Boolean False )
                        , ( "all_awardings" , Array [] )
                        , ( "awarders" , Array [] )
                        , ( "media_only" , Boolean False )
                        , ( "can_gild" , Boolean False )
                        , ( "spoiler" , Boolean False )
                        , ( "locked" , Boolean False )
                        , ( "author_flair_text" , Null )
                        , ( "treatment_tags" , Array [] )
                        , ( "visited" , Boolean False )
                        , ( "removed_by" , Null )
                        , ( "num_reports" , Null )
                        , ( "distinguished" , Null )
                        , ( "subreddit_id" , String "t5_2qh36" )
                        , ( "mod_reason_by" , Null )
                        , ( "removal_reason" , Null )
                        , ( "link_flair_background_color" , String "" )
                        , ( "id" , String "gmte13" )
                        , ( "is_robot_indexable" , Boolean True )
                        , ( "report_reasons" , Null )
                        , ( "author" , String "The-CPMills" )
                        , ( "discussion_type" , Null )
                        , ( "num_comments" , Number (5 % 1) )
                        , ( "send_replies" , Boolean True )
                        , ( "whitelist_status" , String "all_ads" )
                        , ( "contest_mode" , Boolean False )
                        , ( "mod_reports" , Array [] )
                        , ( "author_patreon_flair" , Boolean False )
                        , ( "crosspost_parent" , String "t3_gm53c8" )
                        , ( "author_flair_text_color" , Null )
                        , ( "permalink"
                          , String
                              "/r/haskell/comments/gmte13/i_am_having_difficulty_installing_haskero_for/"
                          )
                        , ( "parent_whitelist_status" , String "all_ads" )
                        , ( "stickied" , Boolean False )
                        , ( "url"
                          , String
                              "/r/vscode/comments/gm53c8/i_am_having_difficulty_installing_haskero/"
                          )
                        , ( "subreddit_subscribers" , Number (55194 % 1) )
                        , ( "created_utc" , Number (1589910314 % 1) )
                        , ( "num_crossposts" , Number (0 % 1) )
                        , ( "media" , Null )
                        , ( "is_video" , Boolean False )
                        ]
                    )
                  ]
              , Object
                  [ ( "kind" , String "t3" )
                  , ( "data"
                    , Object
                        [ ( "approved_at_utc" , Null )
                        , ( "subreddit" , String "haskell" )
                        , ( "selftext" , String "" )
                        , ( "author_fullname" , String "t2_7d9ta" )
                        , ( "saved" , Boolean False )
                        , ( "mod_reason_title" , Null )
                        , ( "gilded" , Number (0 % 1) )
                        , ( "clicked" , Boolean False )
                        , ( "title" , String "[GHC Blog] The state of GHC on ARM" )
                        , ( "link_flair_richtext" , Array [] )
                        , ( "subreddit_name_prefixed" , String "r/haskell" )
                        , ( "hidden" , Boolean False )
                        , ( "pwls" , Number (6 % 1) )
                        , ( "link_flair_css_class" , Null )
                        , ( "downs" , Number (0 % 1) )
                        , ( "hide_score" , Boolean False )
                        , ( "name" , String "t3_gmbfyr" )
                        , ( "quarantine" , Boolean False )
                        , ( "link_flair_text_color" , String "dark" )
                        , ( "upvote_ratio" , Number (2206763817411543 % 2251799813685248) )
                        , ( "author_flair_background_color" , Null )
                        , ( "subreddit_type" , String "public" )
                        , ( "ups" , Number (77 % 1) )
                        , ( "total_awards_received" , Number (0 % 1) )
                        , ( "media_embed" , Object [] )
                        , ( "author_flair_template_id" , Null )
                        , ( "is_original_content" , Boolean False )
                        , ( "user_reports" , Array [] )
                        , ( "secure_media" , Null )
                        , ( "is_reddit_media_domain" , Boolean False )
                        , ( "is_meta" , Boolean False )
                        , ( "category" , Null )
                        , ( "secure_media_embed" , Object [] )
                        , ( "link_flair_text" , Null )
                        , ( "can_mod_post" , Boolean False )
                        , ( "score" , Number (77 % 1) )
                        , ( "approved_by" , Null )
                        , ( "author_premium" , Boolean False )
                        , ( "thumbnail" , String "" )
                        , ( "edited" , Boolean False )
                        , ( "author_flair_css_class" , Null )
                        , ( "author_flair_richtext" , Array [] )
                        , ( "gildings" , Object [] )
                        , ( "content_categories" , Null )
                        , ( "is_self" , Boolean False )
                        , ( "mod_note" , Null )
                        , ( "created" , Number (1589868527 % 1) )
                        , ( "link_flair_type" , String "text" )
                        , ( "wls" , Number (6 % 1) )
                        , ( "removed_by_category" , Null )
                        , ( "banned_by" , Null )
                        , ( "author_flair_type" , String "text" )
                        , ( "domain" , String "haskell.org" )
                        , ( "allow_live_comments" , Boolean False )
                        , ( "selftext_html" , Null )
                        , ( "likes" , Null )
                        , ( "suggested_sort" , Null )
                        , ( "banned_at_utc" , Null )
                        , ( "view_count" , Null )
                        , ( "archived" , Boolean False )
                        , ( "no_follow" , Boolean False )
                        , ( "is_crosspostable" , Boolean False )
                        , ( "pinned" , Boolean False )
                        , ( "over_18" , Boolean False )
                        , ( "all_awardings" , Array [] )
                        , ( "awarders" , Array [] )
                        , ( "media_only" , Boolean False )
                        , ( "can_gild" , Boolean False )
                        , ( "spoiler" , Boolean False )
                        , ( "locked" , Boolean False )
                        , ( "author_flair_text" , Null )
                        , ( "treatment_tags" , Array [] )
                        , ( "visited" , Boolean False )
                        , ( "removed_by" , Null )
                        , ( "num_reports" , Null )
                        , ( "distinguished" , Null )
                        , ( "subreddit_id" , String "t5_2qh36" )
                        , ( "mod_reason_by" , Null )
                        , ( "removal_reason" , Null )
                        , ( "link_flair_background_color" , String "" )
                        , ( "id" , String "gmbfyr" )
                        , ( "is_robot_indexable" , Boolean True )
                        , ( "report_reasons" , Null )
                        , ( "author" , String "bgamari" )
                        , ( "discussion_type" , Null )
                        , ( "num_comments" , Number (9 % 1) )
                        , ( "send_replies" , Boolean True )
                        , ( "whitelist_status" , String "all_ads" )
                        , ( "contest_mode" , Boolean False )
                        , ( "mod_reports" , Array [] )
                        , ( "author_patreon_flair" , Boolean False )
                        , ( "author_flair_text_color" , Null )
                        , ( "permalink"
                          , String
                              "/r/haskell/comments/gmbfyr/ghc_blog_the_state_of_ghc_on_arm/"
                          )
                        , ( "parent_whitelist_status" , String "all_ads" )
                        , ( "stickied" , Boolean False )
                        , ( "url"
                          , String
                              "https://www.haskell.org/ghc/blog/20200515-ghc-on-arm.html"
                          )
                        , ( "subreddit_subscribers" , Number (55194 % 1) )
                        , ( "created_utc" , Number (1589839727 % 1) )
                        , ( "num_crossposts" , Number (1 % 1) )
                        , ( "media" , Null )
                        , ( "is_video" , Boolean False )
                        ]
                    )
                  ]
              , Object
                  [ ( "kind" , String "t3" )
                  , ( "data"
                    , Object
                        [ ( "approved_at_utc" , Null )
                        , ( "subreddit" , String "haskell" )
                        , ( "selftext"
                          , String
                              "I'm trying to build the board for the Peg Solitaire game but I'm stuck. I hope you can help me. The following code runs and generates a square of 3 on 3 circles. How could I make 3 more such squares but put them in other positions? I use the Gloss library. \\n\\n&amp;#x200B;\\n\\n`module Main(main) where` \\n\\n`import Graphics.Gloss` \\n\\n`import Graphics.Gloss.Data.ViewPort` \\n\\n`import` [`Graphics.Gloss.Interface.Pure.Game`](https://Graphics.Gloss.Interface.Pure.Game)\\n\\n `import Data.List`  \\n\\n`width, height, offset :: Int` \\n\\n`width = 400` \\n\\n`height = 400`\\n\\n `offset = 100`  \\n\\n`window :: Display window = InWindow \\\"Peg Solitaire\\\" (width, height) (offset, offset)`\\n\\n  `background :: Color` \\n\\n`background = white`  \\n\\n`drawing :: Picture` \\n\\n`drawing = Pictures [ (translate (x * 40) (y * 40) $ circleSolid 12)| x&lt;-[-1..1], y&lt;-[2..4] ]`  \\n\\n`main = display window background drawing`"
                          )
                        , ( "author_fullname" , String "t2_tewbqxp" )
                        , ( "saved" , Boolean False )
                        , ( "mod_reason_title" , Null )
                        , ( "gilded" , Number (0 % 1) )
                        , ( "clicked" , Boolean False )
                        , ( "title" , String "Drawing the game board in Haskell" )
                        , ( "link_flair_richtext" , Array [] )
                        , ( "subreddit_name_prefixed" , String "r/haskell" )
                        , ( "hidden" , Boolean False )
                        , ( "pwls" , Number (6 % 1) )
                        , ( "link_flair_css_class" , Null )
                        , ( "downs" , Number (0 % 1) )
                        , ( "hide_score" , Boolean False )
                        , ( "name" , String "t3_gmsipz" )
                        , ( "quarantine" , Boolean False )
                        , ( "link_flair_text_color" , String "dark" )
                        , ( "upvote_ratio" , Number (6034823500676465 % 9007199254740992) )
                        , ( "author_flair_background_color" , Null )
                        , ( "subreddit_type" , String "public" )
                        , ( "ups" , Number (2 % 1) )
                        , ( "total_awards_received" , Number (0 % 1) )
                        , ( "media_embed" , Object [] )
                        , ( "author_flair_template_id" , Null )
                        , ( "is_original_content" , Boolean False )
                        , ( "user_reports" , Array [] )
                        , ( "secure_media" , Null )
                        , ( "is_reddit_media_domain" , Boolean False )
                        , ( "is_meta" , Boolean False )
                        , ( "category" , Null )
                        , ( "secure_media_embed" , Object [] )
                        , ( "link_flair_text" , Null )
                        , ( "can_mod_post" , Boolean False )
                        , ( "score" , Number (2 % 1) )
                        , ( "approved_by" , Null )
                        , ( "author_premium" , Boolean False )
                        , ( "thumbnail" , String "" )
                        , ( "edited" , Boolean False )
                        , ( "author_flair_css_class" , Null )
                        , ( "author_flair_richtext" , Array [] )
                        , ( "gildings" , Object [] )
                        , ( "content_categories" , Null )
                        , ( "is_self" , Boolean True )
                        , ( "mod_note" , Null )
                        , ( "created" , Number (1589936485 % 1) )
                        , ( "link_flair_type" , String "text" )
                        , ( "wls" , Number (6 % 1) )
                        , ( "removed_by_category" , Null )
                        , ( "banned_by" , Null )
                        , ( "author_flair_type" , String "text" )
                        , ( "domain" , String "self.haskell" )
                        , ( "allow_live_comments" , Boolean False )
                        , ( "selftext_html"
                          , String
                              "&lt;!-- SC_OFF --&gt;&lt;div class=\\\"md\\\"&gt;&lt;p&gt;I&amp;#39;m trying to build the board for the Peg Solitaire game but I&amp;#39;m stuck. I hope you can help me. The following code runs and generates a square of 3 on 3 circles. How could I make 3 more such squares but put them in other positions? I use the Gloss library. &lt;/p&gt;\\n\\n&lt;p&gt;&amp;#x200B;&lt;/p&gt;\\n\\n&lt;p&gt;&lt;code&gt;module Main(main) where&lt;/code&gt; &lt;/p&gt;\\n\\n&lt;p&gt;&lt;code&gt;import Graphics.Gloss&lt;/code&gt; &lt;/p&gt;\\n\\n&lt;p&gt;&lt;code&gt;import Graphics.Gloss.Data.ViewPort&lt;/code&gt; &lt;/p&gt;\\n\\n&lt;p&gt;&lt;code&gt;import&lt;/code&gt; &lt;a href=\\\"https://Graphics.Gloss.Interface.Pure.Game\\\"&gt;&lt;code&gt;Graphics.Gloss.Interface.Pure.Game&lt;/code&gt;&lt;/a&gt;&lt;/p&gt;\\n\\n&lt;p&gt;&lt;code&gt;import Data.List&lt;/code&gt;  &lt;/p&gt;\\n\\n&lt;p&gt;&lt;code&gt;width, height, offset :: Int&lt;/code&gt; &lt;/p&gt;\\n\\n&lt;p&gt;&lt;code&gt;width = 400&lt;/code&gt; &lt;/p&gt;\\n\\n&lt;p&gt;&lt;code&gt;height = 400&lt;/code&gt;&lt;/p&gt;\\n\\n&lt;p&gt;&lt;code&gt;offset = 100&lt;/code&gt;  &lt;/p&gt;\\n\\n&lt;p&gt;&lt;code&gt;window :: Display window = InWindow &amp;quot;Peg Solitaire&amp;quot; (width, height) (offset, offset)&lt;/code&gt;&lt;/p&gt;\\n\\n&lt;p&gt;&lt;code&gt;background :: Color&lt;/code&gt; &lt;/p&gt;\\n\\n&lt;p&gt;&lt;code&gt;background = white&lt;/code&gt;  &lt;/p&gt;\\n\\n&lt;p&gt;&lt;code&gt;drawing :: Picture&lt;/code&gt; &lt;/p&gt;\\n\\n&lt;p&gt;&lt;code&gt;drawing = Pictures [ (translate (x * 40) (y * 40) $ circleSolid 12)| x&amp;lt;-[-1..1], y&amp;lt;-[2..4] ]&lt;/code&gt;  &lt;/p&gt;\\n\\n&lt;p&gt;&lt;code&gt;main = display window background drawing&lt;/code&gt;&lt;/p&gt;\\n&lt;/div&gt;&lt;!-- SC_ON --&gt;"
                          )
                        , ( "likes" , Null )
                        , ( "suggested_sort" , Null )
                        , ( "banned_at_utc" , Null )
                        , ( "view_count" , Null )
                        , ( "archived" , Boolean False )
                        , ( "no_follow" , Boolean True )
                        , ( "is_crosspostable" , Boolean False )
                        , ( "pinned" , Boolean False )
                        , ( "over_18" , Boolean False )
                        , ( "all_awardings" , Array [] )
                        , ( "awarders" , Array [] )
                        , ( "media_only" , Boolean False )
                        , ( "can_gild" , Boolean False )
                        , ( "spoiler" , Boolean False )
                        , ( "locked" , Boolean False )
                        , ( "author_flair_text" , Null )
                        , ( "treatment_tags" , Array [] )
                        , ( "visited" , Boolean False )
                        , ( "removed_by" , Null )
                        , ( "num_reports" , Null )
                        , ( "distinguished" , Null )
                        , ( "subreddit_id" , String "t5_2qh36" )
                        , ( "mod_reason_by" , Null )
                        , ( "removal_reason" , Null )
                        , ( "link_flair_background_color" , String "" )
                        , ( "id" , String "gmsipz" )
                        , ( "is_robot_indexable" , Boolean True )
                        , ( "report_reasons" , Null )
                        , ( "author" , String "radu23" )
                        , ( "discussion_type" , Null )
                        , ( "num_comments" , Number (11 % 1) )
                        , ( "send_replies" , Boolean True )
                        , ( "whitelist_status" , String "all_ads" )
                        , ( "contest_mode" , Boolean False )
                        , ( "mod_reports" , Array [] )
                        , ( "author_patreon_flair" , Boolean False )
                        , ( "author_flair_text_color" , Null )
                        , ( "permalink"
                          , String
                              "/r/haskell/comments/gmsipz/drawing_the_game_board_in_haskell/"
                          )
                        , ( "parent_whitelist_status" , String "all_ads" )
                        , ( "stickied" , Boolean False )
                        , ( "url"
                          , String
                              "https://old.reddit.com/r/haskell/comments/gmsipz/drawing_the_game_board_in_haskell/"
                          )
                        , ( "subreddit_subscribers" , Number (55194 % 1) )
                        , ( "created_utc" , Number (1589907685 % 1) )
                        , ( "num_crossposts" , Number (0 % 1) )
                        , ( "media" , Null )
                        , ( "is_video" , Boolean False )
                        ]
                    )
                  ]
              , Object
                  [ ( "kind" , String "t3" )
                  , ( "data"
                    , Object
                        [ ( "approved_at_utc" , Null )
                        , ( "subreddit" , String "haskell" )
                        , ( "selftext" , String "" )
                        , ( "author_fullname" , String "t2_jxviuup" )
                        , ( "saved" , Boolean False )
                        , ( "mod_reason_title" , Null )
                        , ( "gilded" , Number (0 % 1) )
                        , ( "clicked" , Boolean False )
                        , ( "title"
                          , String
                              "Presentation on Purely Functional Data Structures - Donnacha Ois\\u00edn Kidney"
                          )
                        , ( "link_flair_richtext" , Array [] )
                        , ( "subreddit_name_prefixed" , String "r/haskell" )
                        , ( "hidden" , Boolean False )
                        , ( "pwls" , Number (6 % 1) )
                        , ( "link_flair_css_class" , Null )
                        , ( "downs" , Number (0 % 1) )
                        , ( "hide_score" , Boolean False )
                        , ( "name" , String "t3_gmen1i" )
                        , ( "quarantine" , Boolean False )
                        , ( "link_flair_text_color" , String "dark" )
                        , ( "upvote_ratio" , Number (4278419646001971 % 4503599627370496) )
                        , ( "author_flair_background_color" , Null )
                        , ( "subreddit_type" , String "public" )
                        , ( "ups" , Number (25 % 1) )
                        , ( "total_awards_received" , Number (0 % 1) )
                        , ( "media_embed" , Object [] )
                        , ( "author_flair_template_id" , Null )
                        , ( "is_original_content" , Boolean False )
                        , ( "user_reports" , Array [] )
                        , ( "secure_media" , Null )
                        , ( "is_reddit_media_domain" , Boolean False )
                        , ( "is_meta" , Boolean False )
                        , ( "category" , Null )
                        , ( "secure_media_embed" , Object [] )
                        , ( "link_flair_text" , Null )
                        , ( "can_mod_post" , Boolean False )
                        , ( "score" , Number (25 % 1) )
                        , ( "approved_by" , Null )
                        , ( "author_premium" , Boolean False )
                        , ( "thumbnail" , String "" )
                        , ( "edited" , Boolean False )
                        , ( "author_flair_css_class" , Null )
                        , ( "author_flair_richtext" , Array [] )
                        , ( "gildings" , Object [] )
                        , ( "content_categories" , Null )
                        , ( "is_self" , Boolean False )
                        , ( "mod_note" , Null )
                        , ( "created" , Number (1589879479 % 1) )
                        , ( "link_flair_type" , String "text" )
                        , ( "wls" , Number (6 % 1) )
                        , ( "removed_by_category" , Null )
                        , ( "banned_by" , Null )
                        , ( "author_flair_type" , String "text" )
                        , ( "domain" , String "doisinkidney.com" )
                        , ( "allow_live_comments" , Boolean False )
                        , ( "selftext_html" , Null )
                        , ( "likes" , Null )
                        , ( "suggested_sort" , Null )
                        , ( "banned_at_utc" , Null )
                        , ( "view_count" , Null )
                        , ( "archived" , Boolean False )
                        , ( "no_follow" , Boolean False )
                        , ( "is_crosspostable" , Boolean False )
                        , ( "pinned" , Boolean False )
                        , ( "over_18" , Boolean False )
                        , ( "all_awardings" , Array [] )
                        , ( "awarders" , Array [] )
                        , ( "media_only" , Boolean False )
                        , ( "can_gild" , Boolean False )
                        , ( "spoiler" , Boolean False )
                        , ( "locked" , Boolean False )
                        , ( "author_flair_text" , Null )
                        , ( "treatment_tags" , Array [] )
                        , ( "visited" , Boolean False )
                        , ( "removed_by" , Null )
                        , ( "num_reports" , Null )
                        , ( "distinguished" , Null )
                        , ( "subreddit_id" , String "t5_2qh36" )
                        , ( "mod_reason_by" , Null )
                        , ( "removal_reason" , Null )
                        , ( "link_flair_background_color" , String "" )
                        , ( "id" , String "gmen1i" )
                        , ( "is_robot_indexable" , Boolean True )
                        , ( "report_reasons" , Null )
                        , ( "author" , String "iedoub" )
                        , ( "discussion_type" , Null )
                        , ( "num_comments" , Number (12 % 1) )
                        , ( "send_replies" , Boolean True )
                        , ( "whitelist_status" , String "all_ads" )
                        , ( "contest_mode" , Boolean False )
                        , ( "mod_reports" , Array [] )
                        , ( "author_patreon_flair" , Boolean False )
                        , ( "author_flair_text_color" , Null )
                        , ( "permalink"
                          , String
                              "/r/haskell/comments/gmen1i/presentation_on_purely_functional_data_structures/"
                          )
                        , ( "parent_whitelist_status" , String "all_ads" )
                        , ( "stickied" , Boolean False )
                        , ( "url"
                          , String
                              "https://doisinkidney.com/posts/2020-05-19-purely-functional-data-structures-slides.html"
                          )
                        , ( "subreddit_subscribers" , Number (55194 % 1) )
                        , ( "created_utc" , Number (1589850679 % 1) )
                        , ( "num_crossposts" , Number (0 % 1) )
                        , ( "media" , Null )
                        , ( "is_video" , Boolean False )
                        ]
                    )
                  ]
              , Object
                  [ ( "kind" , String "t3" )
                  , ( "data"
                    , Object
                        [ ( "approved_at_utc" , Null )
                        , ( "subreddit" , String "haskell" )
                        , ( "selftext"
                          , String
                              "I created a project with stack. Most of the time during the project I used the .cabal file to add dependencies. And that worked fine. However when adding the dependency for a sat-solver I got the following error\\n\\n```\\nminisat-solver needed, but the stack configuration has no specified version  (latest matching version\\n               is 0.1)\\n```\\n\\nTo solve this error I added the line\\n\\n```\\n - minisat-solver-0.1@sha256:e2ff11b1ca8c66e43f8bb2e04f21bd1b812efb94ff215d74f998c928e7e92dcd,5210\\n```\\n\\nto my .yaml file.\\n\\nNow whenever I use `stack build` I get the error\\n\\n```\\n....cabal was modified manually Ignoring ...package.yaml in favor of the cabal file.\\nIf you want to use the package.yaml file instead of the cabal file,\\nthen please delete the cabal file.\\n```\\n\\nHow should I solve this? Should I just delete the .cabal file? What changes should I make to .yaml file\\n\\n--\\n\\nThe .yaml flie\\n\\n```\\n# This file was automatically generated by 'stack init'\\n#\\n# Some commonly used options have been documented as comments in this file.\\n# For advanced use and comprehensive documentation of the format, please see:\\n# https://docs.haskellstack.org/en/stable/yaml_configuration/\\n\\n# Resolver to choose a 'specific' stackage snapshot or a compiler version.\\n# A snapshot resolver dictates the compiler version and the set of packages\\n# to be used for project dependencies. For example:\\n#\\n# resolver: lts-3.5\\n# resolver: nightly-2015-09-21\\n# resolver: ghc-7.10.2\\n#\\n# The location of a snapshot can be provided as a file or url. Stack assumes\\n# a snapshot provided as a file might change, whereas a url resource does not.\\n#\\n# resolver: ./custom-snapshot.yaml\\n# resolver: https://example.com/snapshots/2018-01-01.yaml\\nresolver: lts-14.20\\n\\n# User packages to be built.\\n# Various formats can be used as shown in the example below.\\n#\\n# packages:\\n# - some-directory\\n# - https://example.com/foo/bar/baz-0.0.2.tar.gz\\n#   subdirs:\\n#   - auto-update\\n#   - wai\\npackages:\\n- .\\n# Dependency packages to be pulled from upstream that are not in the resolver.\\n# These entries can reference officially published versions as well as\\n# forks / in-progress versions pinned to a git hash. For example:\\n#\\n# extra-deps:\\n# - acme-missiles-0.3\\n# - git: https://github.com/commercialhaskell/stack.git\\n#   commit: e7b331f14bcffb8367cd58fbfc8b40ec7642100a\\n#\\n# extra-deps: []\\n\\n# Override default flag values for local packages and extra-deps\\n# flags: {}\\n\\n# Extra package databases containing global packages\\n# extra-package-dbs: []\\n\\n# Control whether we use the GHC we find on the path\\n# system-ghc: true\\n#\\n# Require a specific version of stack, using version ranges\\n# require-stack-version: -any # Default\\n# require-stack-version: \\\"&gt;=2.1\\\"\\n#\\n# Override the architecture used by stack, especially useful on Windows\\n# arch: i386\\n# arch: x86_64\\n#\\n# Extra directories used by stack for building\\n# extra-include-dirs: [/path/to/dir]\\n# extra-lib-dirs: [/path/to/dir]\\n#\\n# Allow a newer minor version of GHC than the snapshot specifies\\n# compiler-check: newer-minor\\n\\nextra-deps:\\n - minisat-solver-0.1@sha256:e2ff11b1ca8c66e43f8bb2e04f21bd1b812efb94ff215d74f998c928e7e92dcd,5210\\n\\n```\\n\\nThe cabal file\\n\\n```\\ncabal-version: 1.12\\n\\n-- This file has been generated from package.yaml by hpack version 0.31.2.\\n--\\n-- see: https://github.com/sol/hpack\\n--\\n-- hash: 9e4c1b8d2c640f6364c7abf13e184823a0c4b7959a05310c93a9b6ff92efad16\\n\\nname:           dtl-model-checking\\nversion:        0.1.0.0\\ndescription:    Please see the README on GitHub at &lt;https://github.com/githubuser/dtl-model-checking#readme&gt;\\nhomepage:       https://github.com/githubuser/dtl-model-checking#readme\\nbug-reports:    https://github.com/githubuser/dtl-model-checking/issues\\nauthor:         Author name here\\nmaintainer:     example@example.com\\ncopyright:      2020 Author name here\\nlicense:        BSD3\\nlicense-file:   LICENSE\\nbuild-type:     Simple\\nextra-source-files:\\n    README.md\\n    ChangeLog.md\\n\\nsource-repository head\\n  type: git\\n  location: https://github.com/githubuser/dtl-model-checking\\n\\nlibrary\\n  exposed-modules:\\n      Automaton\\n      DTLFormula\\n      AutomataTheoreticApproach\\n      DTS\\n      NBA\\n      GNBA\\n      Ielementary\\n      CommonTypes\\n      Utils\\n      ExampleInstances\\n      BMC\\n  other-modules:\\n      Paths_dtl_model_checking\\n  hs-source-dirs:\\n      src\\n  build-depends:\\n      base &gt;=4.7 &amp;&amp; &lt;5\\n    , containers\\n    , random\\n    , minisat-solver &gt;= 0.1\\n  default-language: Haskell2010\\n\\nexecutable dtl-model-checking-exe\\n  main-is: Main.hs\\n  other-modules:\\n      Paths_dtl_model_checking\\n  hs-source-dirs:\\n      app\\n  ghc-options: -O -threaded -rtsopts -with-rtsopts=-N\\n  build-depends:\\n      base &gt;=4.7 &amp;&amp; &lt;5\\n    , dtl-model-checking\\n    , containers\\n    , random\\n  default-language: Haskell2010\\n\\ntest-suite dtl-model-checking-test\\n  type: exitcode-stdio-1.0\\n  main-is: Spec.hs\\n  other-modules:\\n      Paths_dtl_model_checking\\n  hs-source-dirs:\\n      test\\n  ghc-options: -O -threaded -rtsopts -with-rtsopts=-N\\n  build-depends:\\n      base &gt;=4.7 &amp;&amp; &lt;5\\n    , dtl-model-checking\\n    , containers\\n    , hspec\\n    , random\\n  default-language: Haskell2010\\n\\nbenchmark dtl-model-checking-benchmark\\n  type: exitcode-stdio-1.0 \\n  main-is: Bench.hs\\n  other-modules:\\n      Paths_dtl_model_checking\\n  hs-source-dirs:\\n      benchmark\\n  ghc-options: -O -threaded -fforce-recomp -rtsopts -with-rtsopts=-N\\n  build-depends: base &gt;=4.7 &amp;&amp; &lt;5, dtl-model-checking, containers, criterion, random\\n  default-language: Haskell2010\\n```"
                          )
                        , ( "author_fullname" , String "t2_u7qgp4w" )
                        , ( "saved" , Boolean False )
                        , ( "mod_reason_title" , Null )
                        , ( "gilded" , Number (0 % 1) )
                        , ( "clicked" , Boolean False )
                        , ( "title" , String "Error/warning on stack build" )
                        , ( "link_flair_richtext" , Array [] )
                        , ( "subreddit_name_prefixed" , String "r/haskell" )
                        , ( "hidden" , Boolean False )
                        , ( "pwls" , Number (6 % 1) )
                        , ( "link_flair_css_class" , Null )
                        , ( "downs" , Number (0 % 1) )
                        , ( "hide_score" , Boolean False )
                        , ( "name" , String "t3_gmoik7" )
                        , ( "quarantine" , Boolean False )
                        , ( "link_flair_text_color" , String "dark" )
                        , ( "upvote_ratio" , Number (1 % 2) )
                        , ( "author_flair_background_color" , Null )
                        , ( "subreddit_type" , String "public" )
                        , ( "ups" , Number (0 % 1) )
                        , ( "total_awards_received" , Number (0 % 1) )
                        , ( "media_embed" , Object [] )
                        , ( "author_flair_template_id" , Null )
                        , ( "is_original_content" , Boolean False )
                        , ( "user_reports" , Array [] )
                        , ( "secure_media" , Null )
                        , ( "is_reddit_media_domain" , Boolean False )
                        , ( "is_meta" , Boolean False )
                        , ( "category" , Null )
                        , ( "secure_media_embed" , Object [] )
                        , ( "link_flair_text" , Null )
                        , ( "can_mod_post" , Boolean False )
                        , ( "score" , Number (0 % 1) )
                        , ( "approved_by" , Null )
                        , ( "author_premium" , Boolean False )
                        , ( "thumbnail" , String "" )
                        , ( "edited" , Boolean False )
                        , ( "author_flair_css_class" , Null )
                        , ( "author_flair_richtext" , Array [] )
                        , ( "gildings" , Object [] )
                        , ( "content_categories" , Null )
                        , ( "is_self" , Boolean True )
                        , ( "mod_note" , Null )
                        , ( "created" , Number (1589923554 % 1) )
                        , ( "link_flair_type" , String "text" )
                        , ( "wls" , Number (6 % 1) )
                        , ( "removed_by_category" , Null )
                        , ( "banned_by" , Null )
                        , ( "author_flair_type" , String "text" )
                        , ( "domain" , String "self.haskell" )
                        , ( "allow_live_comments" , Boolean False )
                        , ( "selftext_html"
                          , String
                              "&lt;!-- SC_OFF --&gt;&lt;div class=\\\"md\\\"&gt;&lt;p&gt;I created a project with stack. Most of the time during the project I used the .cabal file to add dependencies. And that worked fine. However when adding the dependency for a sat-solver I got the following error&lt;/p&gt;\\n\\n&lt;p&gt;&lt;code&gt;\\nminisat-solver needed, but the stack configuration has no specified version  (latest matching version\\n               is 0.1)\\n&lt;/code&gt;&lt;/p&gt;\\n\\n&lt;p&gt;To solve this error I added the line&lt;/p&gt;\\n\\n&lt;p&gt;&lt;code&gt;\\n - minisat-solver-0.1@sha256:e2ff11b1ca8c66e43f8bb2e04f21bd1b812efb94ff215d74f998c928e7e92dcd,5210\\n&lt;/code&gt;&lt;/p&gt;\\n\\n&lt;p&gt;to my .yaml file.&lt;/p&gt;\\n\\n&lt;p&gt;Now whenever I use &lt;code&gt;stack build&lt;/code&gt; I get the error&lt;/p&gt;\\n\\n&lt;p&gt;&lt;code&gt;\\n....cabal was modified manually Ignoring ...package.yaml in favor of the cabal file.\\nIf you want to use the package.yaml file instead of the cabal file,\\nthen please delete the cabal file.\\n&lt;/code&gt;&lt;/p&gt;\\n\\n&lt;p&gt;How should I solve this? Should I just delete the .cabal file? What changes should I make to .yaml file&lt;/p&gt;\\n\\n&lt;h2&gt;&lt;/h2&gt;\\n\\n&lt;p&gt;The .yaml flie&lt;/p&gt;\\n\\n&lt;p&gt;```&lt;/p&gt;\\n\\n&lt;h1&gt;This file was automatically generated by &amp;#39;stack init&amp;#39;&lt;/h1&gt;\\n\\n&lt;h1&gt;Some commonly used options have been documented as comments in this file.&lt;/h1&gt;\\n\\n&lt;h1&gt;For advanced use and comprehensive documentation of the format, please see:&lt;/h1&gt;\\n\\n&lt;h1&gt;&lt;a href=\\\"https://docs.haskellstack.org/en/stable/yaml_configuration/\\\"&gt;https://docs.haskellstack.org/en/stable/yaml_configuration/&lt;/a&gt;&lt;/h1&gt;\\n\\n&lt;h1&gt;Resolver to choose a &amp;#39;specific&amp;#39; stackage snapshot or a compiler version.&lt;/h1&gt;\\n\\n&lt;h1&gt;A snapshot resolver dictates the compiler version and the set of packages&lt;/h1&gt;\\n\\n&lt;h1&gt;to be used for project dependencies. For example:&lt;/h1&gt;\\n\\n&lt;h1&gt;resolver: lts-3.5&lt;/h1&gt;\\n\\n&lt;h1&gt;resolver: nightly-2015-09-21&lt;/h1&gt;\\n\\n&lt;h1&gt;resolver: ghc-7.10.2&lt;/h1&gt;\\n\\n&lt;h1&gt;The location of a snapshot can be provided as a file or url. Stack assumes&lt;/h1&gt;\\n\\n&lt;h1&gt;a snapshot provided as a file might change, whereas a url resource does not.&lt;/h1&gt;\\n\\n&lt;h1&gt;resolver: ./custom-snapshot.yaml&lt;/h1&gt;\\n\\n&lt;h1&gt;resolver: &lt;a href=\\\"https://example.com/snapshots/2018-01-01.yaml\\\"&gt;https://example.com/snapshots/2018-01-01.yaml&lt;/a&gt;&lt;/h1&gt;\\n\\n&lt;p&gt;resolver: lts-14.20&lt;/p&gt;\\n\\n&lt;h1&gt;User packages to be built.&lt;/h1&gt;\\n\\n&lt;h1&gt;Various formats can be used as shown in the example below.&lt;/h1&gt;\\n\\n&lt;h1&gt;packages:&lt;/h1&gt;\\n\\n&lt;h1&gt;- some-directory&lt;/h1&gt;\\n\\n&lt;h1&gt;- &lt;a href=\\\"https://example.com/foo/bar/baz-0.0.2.tar.gz\\\"&gt;https://example.com/foo/bar/baz-0.0.2.tar.gz&lt;/a&gt;&lt;/h1&gt;\\n\\n&lt;h1&gt;subdirs:&lt;/h1&gt;\\n\\n&lt;h1&gt;- auto-update&lt;/h1&gt;\\n\\n&lt;h1&gt;- wai&lt;/h1&gt;\\n\\n&lt;p&gt;packages:\\n- .&lt;/p&gt;\\n\\n&lt;h1&gt;Dependency packages to be pulled from upstream that are not in the resolver.&lt;/h1&gt;\\n\\n&lt;h1&gt;These entries can reference officially published versions as well as&lt;/h1&gt;\\n\\n&lt;h1&gt;forks / in-progress versions pinned to a git hash. For example:&lt;/h1&gt;\\n\\n&lt;h1&gt;extra-deps:&lt;/h1&gt;\\n\\n&lt;h1&gt;- acme-missiles-0.3&lt;/h1&gt;\\n\\n&lt;h1&gt;- git: &lt;a href=\\\"https://github.com/commercialhaskell/stack.git\\\"&gt;https://github.com/commercialhaskell/stack.git&lt;/a&gt;&lt;/h1&gt;\\n\\n&lt;h1&gt;commit: e7b331f14bcffb8367cd58fbfc8b40ec7642100a&lt;/h1&gt;\\n\\n&lt;h1&gt;extra-deps: []&lt;/h1&gt;\\n\\n&lt;h1&gt;Override default flag values for local packages and extra-deps&lt;/h1&gt;\\n\\n&lt;h1&gt;flags: {}&lt;/h1&gt;\\n\\n&lt;h1&gt;Extra package databases containing global packages&lt;/h1&gt;\\n\\n&lt;h1&gt;extra-package-dbs: []&lt;/h1&gt;\\n\\n&lt;h1&gt;Control whether we use the GHC we find on the path&lt;/h1&gt;\\n\\n&lt;h1&gt;system-ghc: true&lt;/h1&gt;\\n\\n&lt;h1&gt;Require a specific version of stack, using version ranges&lt;/h1&gt;\\n\\n&lt;h1&gt;require-stack-version: -any # Default&lt;/h1&gt;\\n\\n&lt;h1&gt;require-stack-version: &amp;quot;&amp;gt;=2.1&amp;quot;&lt;/h1&gt;\\n\\n&lt;h1&gt;Override the architecture used by stack, especially useful on Windows&lt;/h1&gt;\\n\\n&lt;h1&gt;arch: i386&lt;/h1&gt;\\n\\n&lt;h1&gt;arch: x86_64&lt;/h1&gt;\\n\\n&lt;h1&gt;Extra directories used by stack for building&lt;/h1&gt;\\n\\n&lt;h1&gt;extra-include-dirs: [/path/to/dir]&lt;/h1&gt;\\n\\n&lt;h1&gt;extra-lib-dirs: [/path/to/dir]&lt;/h1&gt;\\n\\n&lt;h1&gt;Allow a newer minor version of GHC than the snapshot specifies&lt;/h1&gt;\\n\\n&lt;h1&gt;compiler-check: newer-minor&lt;/h1&gt;\\n\\n&lt;p&gt;extra-deps:\\n - minisat-solver-0.1@sha256:e2ff11b1ca8c66e43f8bb2e04f21bd1b812efb94ff215d74f998c928e7e92dcd,5210&lt;/p&gt;\\n\\n&lt;p&gt;```&lt;/p&gt;\\n\\n&lt;p&gt;The cabal file&lt;/p&gt;\\n\\n&lt;p&gt;```\\ncabal-version: 1.12&lt;/p&gt;\\n\\n&lt;h2&gt;-- This file has been generated from package.yaml by hpack version 0.31.2.&lt;/h2&gt;\\n\\n&lt;h2&gt;-- see: &lt;a href=\\\"https://github.com/sol/hpack\\\"&gt;https://github.com/sol/hpack&lt;/a&gt;&lt;/h2&gt;\\n\\n&lt;p&gt;-- hash: 9e4c1b8d2c640f6364c7abf13e184823a0c4b7959a05310c93a9b6ff92efad16&lt;/p&gt;\\n\\n&lt;p&gt;name:           dtl-model-checking\\nversion:        0.1.0.0\\ndescription:    Please see the README on GitHub at &lt;a href=\\\"https://github.com/githubuser/dtl-model-checking#readme\\\"&gt;https://github.com/githubuser/dtl-model-checking#readme&lt;/a&gt;\\nhomepage:       &lt;a href=\\\"https://github.com/githubuser/dtl-model-checking#readme\\\"&gt;https://github.com/githubuser/dtl-model-checking#readme&lt;/a&gt;\\nbug-reports:    &lt;a href=\\\"https://github.com/githubuser/dtl-model-checking/issues\\\"&gt;https://github.com/githubuser/dtl-model-checking/issues&lt;/a&gt;\\nauthor:         Author name here\\nmaintainer:     &lt;a href=\\\"mailto:example@example.com\\\"&gt;example@example.com&lt;/a&gt;\\ncopyright:      2020 Author name here\\nlicense:        BSD3\\nlicense-file:   LICENSE\\nbuild-type:     Simple\\nextra-source-files:\\n    README.md\\n    ChangeLog.md&lt;/p&gt;\\n\\n&lt;p&gt;source-repository head\\n  type: git\\n  location: &lt;a href=\\\"https://github.com/githubuser/dtl-model-checking\\\"&gt;https://github.com/githubuser/dtl-model-checking&lt;/a&gt;&lt;/p&gt;\\n\\n&lt;p&gt;library\\n  exposed-modules:\\n      Automaton\\n      DTLFormula\\n      AutomataTheoreticApproach\\n      DTS\\n      NBA\\n      GNBA\\n      Ielementary\\n      CommonTypes\\n      Utils\\n      ExampleInstances\\n      BMC\\n  other-modules:\\n      Paths_dtl_model_checking\\n  hs-source-dirs:\\n      src\\n  build-depends:\\n      base &amp;gt;=4.7 &amp;amp;&amp;amp; &amp;lt;5\\n    , containers\\n    , random\\n    , minisat-solver &amp;gt;= 0.1\\n  default-language: Haskell2010&lt;/p&gt;\\n\\n&lt;p&gt;executable dtl-model-checking-exe\\n  main-is: Main.hs\\n  other-modules:\\n      Paths_dtl_model_checking\\n  hs-source-dirs:\\n      app\\n  ghc-options: -O -threaded -rtsopts -with-rtsopts=-N\\n  build-depends:\\n      base &amp;gt;=4.7 &amp;amp;&amp;amp; &amp;lt;5\\n    , dtl-model-checking\\n    , containers\\n    , random\\n  default-language: Haskell2010&lt;/p&gt;\\n\\n&lt;p&gt;test-suite dtl-model-checking-test\\n  type: exitcode-stdio-1.0\\n  main-is: Spec.hs\\n  other-modules:\\n      Paths_dtl_model_checking\\n  hs-source-dirs:\\n      test\\n  ghc-options: -O -threaded -rtsopts -with-rtsopts=-N\\n  build-depends:\\n      base &amp;gt;=4.7 &amp;amp;&amp;amp; &amp;lt;5\\n    , dtl-model-checking\\n    , containers\\n    , hspec\\n    , random\\n  default-language: Haskell2010&lt;/p&gt;\\n\\n&lt;p&gt;benchmark dtl-model-checking-benchmark\\n  type: exitcode-stdio-1.0 \\n  main-is: Bench.hs\\n  other-modules:\\n      Paths_dtl_model_checking\\n  hs-source-dirs:\\n      benchmark\\n  ghc-options: -O -threaded -fforce-recomp -rtsopts -with-rtsopts=-N\\n  build-depends: base &amp;gt;=4.7 &amp;amp;&amp;amp; &amp;lt;5, dtl-model-checking, containers, criterion, random\\n  default-language: Haskell2010\\n```&lt;/p&gt;\\n&lt;/div&gt;&lt;!-- SC_ON --&gt;"
                          )
                        , ( "likes" , Null )
                        , ( "suggested_sort" , Null )
                        , ( "banned_at_utc" , Null )
                        , ( "view_count" , Null )
                        , ( "archived" , Boolean False )
                        , ( "no_follow" , Boolean True )
                        , ( "is_crosspostable" , Boolean False )
                        , ( "pinned" , Boolean False )
                        , ( "over_18" , Boolean False )
                        , ( "all_awardings" , Array [] )
                        , ( "awarders" , Array [] )
                        , ( "media_only" , Boolean False )
                        , ( "can_gild" , Boolean False )
                        , ( "spoiler" , Boolean False )
                        , ( "locked" , Boolean False )
                        , ( "author_flair_text" , Null )
                        , ( "treatment_tags" , Array [] )
                        , ( "visited" , Boolean False )
                        , ( "removed_by" , Null )
                        , ( "num_reports" , Null )
                        , ( "distinguished" , Null )
                        , ( "subreddit_id" , String "t5_2qh36" )
                        , ( "mod_reason_by" , Null )
                        , ( "removal_reason" , Null )
                        , ( "link_flair_background_color" , String "" )
                        , ( "id" , String "gmoik7" )
                        , ( "is_robot_indexable" , Boolean True )
                        , ( "report_reasons" , Null )
                        , ( "author" , String "augustoperes" )
                        , ( "discussion_type" , Null )
                        , ( "num_comments" , Number (2 % 1) )
                        , ( "send_replies" , Boolean True )
                        , ( "whitelist_status" , String "all_ads" )
                        , ( "contest_mode" , Boolean False )
                        , ( "mod_reports" , Array [] )
                        , ( "author_patreon_flair" , Boolean False )
                        , ( "author_flair_text_color" , Null )
                        , ( "permalink"
                          , String "/r/haskell/comments/gmoik7/errorwarning_on_stack_build/"
                          )
                        , ( "parent_whitelist_status" , String "all_ads" )
                        , ( "stickied" , Boolean False )
                        , ( "url"
                          , String
                              "https://old.reddit.com/r/haskell/comments/gmoik7/errorwarning_on_stack_build/"
                          )
                        , ( "subreddit_subscribers" , Number (55194 % 1) )
                        , ( "created_utc" , Number (1589894754 % 1) )
                        , ( "num_crossposts" , Number (0 % 1) )
                        , ( "media" , Null )
                        , ( "is_video" , Boolean False )
                        ]
                    )
                  ]
              , Object
                  [ ( "kind" , String "t3" )
                  , ( "data"
                    , Object
                        [ ( "approved_at_utc" , Null )
                        , ( "subreddit" , String "haskell" )
                        , ( "selftext"
                          , String
                              "Do you have any examples of libraries in other languages or language features, which really should have implemented a well-known concept (Monoid, Monad, Alternative, whatever), but they fell short because they (probably) didn't know the concept? For example a broken law, a missing function, over-complicated function types, etc.\\n\\nI encountered multiple such examples, and they always grind my gears. But for the life of me, I can't remember any of them now."
                          )
                        , ( "author_fullname" , String "t2_b7rje" )
                        , ( "saved" , Boolean False )
                        , ( "mod_reason_title" , Null )
                        , ( "gilded" , Number (0 % 1) )
                        , ( "clicked" , Boolean False )
                        , ( "title"
                          , String "Examples of Incorrect Abstractions in Other Languages"
                          )
                        , ( "link_flair_richtext" , Array [] )
                        , ( "subreddit_name_prefixed" , String "r/haskell" )
                        , ( "hidden" , Boolean False )
                        , ( "pwls" , Number (6 % 1) )
                        , ( "link_flair_css_class" , Null )
                        , ( "downs" , Number (0 % 1) )
                        , ( "hide_score" , Boolean False )
                        , ( "name" , String "t3_glz389" )
                        , ( "quarantine" , Boolean False )
                        , ( "link_flair_text_color" , String "dark" )
                        , ( "upvote_ratio" , Number (4368491638549381 % 4503599627370496) )
                        , ( "author_flair_background_color" , Null )
                        , ( "subreddit_type" , String "public" )
                        , ( "ups" , Number (102 % 1) )
                        , ( "total_awards_received" , Number (0 % 1) )
                        , ( "media_embed" , Object [] )
                        , ( "author_flair_template_id" , Null )
                        , ( "is_original_content" , Boolean False )
                        , ( "user_reports" , Array [] )
                        , ( "secure_media" , Null )
                        , ( "is_reddit_media_domain" , Boolean False )
                        , ( "is_meta" , Boolean False )
                        , ( "category" , Null )
                        , ( "secure_media_embed" , Object [] )
                        , ( "link_flair_text" , Null )
                        , ( "can_mod_post" , Boolean False )
                        , ( "score" , Number (102 % 1) )
                        , ( "approved_by" , Null )
                        , ( "author_premium" , Boolean False )
                        , ( "thumbnail" , String "" )
                        , ( "edited" , Boolean False )
                        , ( "author_flair_css_class" , Null )
                        , ( "author_flair_richtext" , Array [] )
                        , ( "gildings" , Object [] )
                        , ( "content_categories" , Null )
                        , ( "is_self" , Boolean True )
                        , ( "mod_note" , Null )
                        , ( "created" , Number (1589827048 % 1) )
                        , ( "link_flair_type" , String "text" )
                        , ( "wls" , Number (6 % 1) )
                        , ( "removed_by_category" , Null )
                        , ( "banned_by" , Null )
                        , ( "author_flair_type" , String "text" )
                        , ( "domain" , String "self.haskell" )
                        , ( "allow_live_comments" , Boolean False )
                        , ( "selftext_html"
                          , String
                              "&lt;!-- SC_OFF --&gt;&lt;div class=\\\"md\\\"&gt;&lt;p&gt;Do you have any examples of libraries in other languages or language features, which really should have implemented a well-known concept (Monoid, Monad, Alternative, whatever), but they fell short because they (probably) didn&amp;#39;t know the concept? For example a broken law, a missing function, over-complicated function types, etc.&lt;/p&gt;\\n\\n&lt;p&gt;I encountered multiple such examples, and they always grind my gears. But for the life of me, I can&amp;#39;t remember any of them now.&lt;/p&gt;\\n&lt;/div&gt;&lt;!-- SC_ON --&gt;"
                          )
                        , ( "likes" , Null )
                        , ( "suggested_sort" , Null )
                        , ( "banned_at_utc" , Null )
                        , ( "view_count" , Null )
                        , ( "archived" , Boolean False )
                        , ( "no_follow" , Boolean False )
                        , ( "is_crosspostable" , Boolean False )
                        , ( "pinned" , Boolean False )
                        , ( "over_18" , Boolean False )
                        , ( "all_awardings" , Array [] )
                        , ( "awarders" , Array [] )
                        , ( "media_only" , Boolean False )
                        , ( "can_gild" , Boolean False )
                        , ( "spoiler" , Boolean False )
                        , ( "locked" , Boolean False )
                        , ( "author_flair_text" , Null )
                        , ( "treatment_tags" , Array [] )
                        , ( "visited" , Boolean False )
                        , ( "removed_by" , Null )
                        , ( "num_reports" , Null )
                        , ( "distinguished" , Null )
                        , ( "subreddit_id" , String "t5_2qh36" )
                        , ( "mod_reason_by" , Null )
                        , ( "removal_reason" , Null )
                        , ( "link_flair_background_color" , String "" )
                        , ( "id" , String "glz389" )
                        , ( "is_robot_indexable" , Boolean True )
                        , ( "report_reasons" , Null )
                        , ( "author" , String "pavelpotocek" )
                        , ( "discussion_type" , Null )
                        , ( "num_comments" , Number (175 % 1) )
                        , ( "send_replies" , Boolean True )
                        , ( "whitelist_status" , String "all_ads" )
                        , ( "contest_mode" , Boolean False )
                        , ( "mod_reports" , Array [] )
                        , ( "author_patreon_flair" , Boolean False )
                        , ( "author_flair_text_color" , Null )
                        , ( "permalink"
                          , String
                              "/r/haskell/comments/glz389/examples_of_incorrect_abstractions_in_other/"
                          )
                        , ( "parent_whitelist_status" , String "all_ads" )
                        , ( "stickied" , Boolean False )
                        , ( "url"
                          , String
                              "https://old.reddit.com/r/haskell/comments/glz389/examples_of_incorrect_abstractions_in_other/"
                          )
                        , ( "subreddit_subscribers" , Number (55194 % 1) )
                        , ( "created_utc" , Number (1589798248 % 1) )
                        , ( "num_crossposts" , Number (0 % 1) )
                        , ( "media" , Null )
                        , ( "is_video" , Boolean False )
                        ]
                    )
                  ]
              , Object
                  [ ( "kind" , String "t3" )
                  , ( "data"
                    , Object
                        [ ( "approved_at_utc" , Null )
                        , ( "subreddit" , String "haskell" )
                        , ( "selftext" , String "" )
                        , ( "author_fullname" , String "t2_2o6ongui" )
                        , ( "saved" , Boolean False )
                        , ( "mod_reason_title" , Null )
                        , ( "gilded" , Number (0 % 1) )
                        , ( "clicked" , Boolean False )
                        , ( "title" , String "[ANN] Medea - a json schema language" )
                        , ( "link_flair_richtext" , Array [] )
                        , ( "subreddit_name_prefixed" , String "r/haskell" )
                        , ( "hidden" , Boolean False )
                        , ( "pwls" , Number (6 % 1) )
                        , ( "link_flair_css_class" , Null )
                        , ( "downs" , Number (0 % 1) )
                        , ( "hide_score" , Boolean False )
                        , ( "name" , String "t3_gma3p4" )
                        , ( "quarantine" , Boolean False )
                        , ( "link_flair_text_color" , String "dark" )
                        , ( "upvote_ratio" , Number (1 % 1) )
                        , ( "author_flair_background_color" , Null )
                        , ( "subreddit_type" , String "public" )
                        , ( "ups" , Number (14 % 1) )
                        , ( "total_awards_received" , Number (0 % 1) )
                        , ( "media_embed" , Object [] )
                        , ( "author_flair_template_id" , Null )
                        , ( "is_original_content" , Boolean False )
                        , ( "user_reports" , Array [] )
                        , ( "secure_media" , Null )
                        , ( "is_reddit_media_domain" , Boolean False )
                        , ( "is_meta" , Boolean False )
                        , ( "category" , Null )
                        , ( "secure_media_embed" , Object [] )
                        , ( "link_flair_text" , Null )
                        , ( "can_mod_post" , Boolean False )
                        , ( "score" , Number (14 % 1) )
                        , ( "approved_by" , Null )
                        , ( "author_premium" , Boolean False )
                        , ( "thumbnail" , String "" )
                        , ( "edited" , Boolean False )
                        , ( "author_flair_css_class" , Null )
                        , ( "author_flair_richtext" , Array [] )
                        , ( "gildings" , Object [] )
                        , ( "content_categories" , Null )
                        , ( "is_self" , Boolean False )
                        , ( "mod_note" , Null )
                        , ( "created" , Number (1589864384 % 1) )
                        , ( "link_flair_type" , String "text" )
                        , ( "wls" , Number (6 % 1) )
                        , ( "removed_by_category" , Null )
                        , ( "banned_by" , Null )
                        , ( "author_flair_type" , String "text" )
                        , ( "domain" , String "github.com" )
                        , ( "allow_live_comments" , Boolean False )
                        , ( "selftext_html" , Null )
                        , ( "likes" , Null )
                        , ( "suggested_sort" , Null )
                        , ( "banned_at_utc" , Null )
                        , ( "view_count" , Null )
                        , ( "archived" , Boolean False )
                        , ( "no_follow" , Boolean False )
                        , ( "is_crosspostable" , Boolean False )
                        , ( "pinned" , Boolean False )
                        , ( "over_18" , Boolean False )
                        , ( "all_awardings" , Array [] )
                        , ( "awarders" , Array [] )
                        , ( "media_only" , Boolean False )
                        , ( "can_gild" , Boolean False )
                        , ( "spoiler" , Boolean False )
                        , ( "locked" , Boolean False )
                        , ( "author_flair_text" , Null )
                        , ( "treatment_tags" , Array [] )
                        , ( "visited" , Boolean False )
                        , ( "removed_by" , Null )
                        , ( "num_reports" , Null )
                        , ( "distinguished" , Null )
                        , ( "subreddit_id" , String "t5_2qh36" )
                        , ( "mod_reason_by" , Null )
                        , ( "removal_reason" , Null )
                        , ( "link_flair_background_color" , String "" )
                        , ( "id" , String "gma3p4" )
                        , ( "is_robot_indexable" , Boolean True )
                        , ( "report_reasons" , Null )
                        , ( "author" , String "restarted_mustard" )
                        , ( "discussion_type" , Null )
                        , ( "num_comments" , Number (2 % 1) )
                        , ( "send_replies" , Boolean True )
                        , ( "whitelist_status" , String "all_ads" )
                        , ( "contest_mode" , Boolean False )
                        , ( "mod_reports" , Array [] )
                        , ( "author_patreon_flair" , Boolean False )
                        , ( "author_flair_text_color" , Null )
                        , ( "permalink"
                          , String
                              "/r/haskell/comments/gma3p4/ann_medea_a_json_schema_language/"
                          )
                        , ( "parent_whitelist_status" , String "all_ads" )
                        , ( "stickied" , Boolean False )
                        , ( "url" , String "https://github.com/juspay/medea" )
                        , ( "subreddit_subscribers" , Number (55194 % 1) )
                        , ( "created_utc" , Number (1589835584 % 1) )
                        , ( "num_crossposts" , Number (0 % 1) )
                        , ( "media" , Null )
                        , ( "is_video" , Boolean False )
                        ]
                    )
                  ]
              , Object
                  [ ( "kind" , String "t3" )
                  , ( "data"
                    , Object
                        [ ( "approved_at_utc" , Null )
                        , ( "subreddit" , String "haskell" )
                        , ( "selftext"
                          , String
                              "There seem to be some [posts](https://www.reddit.com/r/haskell/comments/pen8s/anyone_else_used_write_yourself_a_scheme_in_48/) about the book or the [Write You a Scheme V2.0](https://wespiser.com/writings/wyas/00_overview.html), but I'm unsure how much Scheme I need to tackle this project.\\n\\nI've thumbed through the (in)famous Learn You a Haskell, and implementing an interpreter sounds like a lot of fun, but perhaps I might not down this path if I have to spend the time to buckle down and learn some Scheme syntax too."
                          )
                        , ( "author_fullname" , String "t2_5y26z8w2" )
                        , ( "saved" , Boolean False )
                        , ( "mod_reason_title" , Null )
                        , ( "gilded" , Number (0 % 1) )
                        , ( "clicked" , Boolean False )
                        , ( "title"
                          , String
                              "How much Scheme needed for \\\"Write yourself a Scheme in 48 hours?\\\""
                          )
                        , ( "link_flair_richtext" , Array [] )
                        , ( "subreddit_name_prefixed" , String "r/haskell" )
                        , ( "hidden" , Boolean False )
                        , ( "pwls" , Number (6 % 1) )
                        , ( "link_flair_css_class" , Null )
                        , ( "downs" , Number (0 % 1) )
                        , ( "hide_score" , Boolean False )
                        , ( "name" , String "t3_gm3ia1" )
                        , ( "quarantine" , Boolean False )
                        , ( "link_flair_text_color" , String "dark" )
                        , ( "upvote_ratio" , Number (4368491638549381 % 4503599627370496) )
                        , ( "author_flair_background_color" , Null )
                        , ( "subreddit_type" , String "public" )
                        , ( "ups" , Number (22 % 1) )
                        , ( "total_awards_received" , Number (0 % 1) )
                        , ( "media_embed" , Object [] )
                        , ( "author_flair_template_id" , Null )
                        , ( "is_original_content" , Boolean False )
                        , ( "user_reports" , Array [] )
                        , ( "secure_media" , Null )
                        , ( "is_reddit_media_domain" , Boolean False )
                        , ( "is_meta" , Boolean False )
                        , ( "category" , Null )
                        , ( "secure_media_embed" , Object [] )
                        , ( "link_flair_text" , Null )
                        , ( "can_mod_post" , Boolean False )
                        , ( "score" , Number (22 % 1) )
                        , ( "approved_by" , Null )
                        , ( "author_premium" , Boolean False )
                        , ( "thumbnail" , String "" )
                        , ( "edited" , Boolean False )
                        , ( "author_flair_css_class" , Null )
                        , ( "author_flair_richtext" , Array [] )
                        , ( "gildings" , Object [] )
                        , ( "content_categories" , Null )
                        , ( "is_self" , Boolean True )
                        , ( "mod_note" , Null )
                        , ( "created" , Number (1589844357 % 1) )
                        , ( "link_flair_type" , String "text" )
                        , ( "wls" , Number (6 % 1) )
                        , ( "removed_by_category" , Null )
                        , ( "banned_by" , Null )
                        , ( "author_flair_type" , String "text" )
                        , ( "domain" , String "self.haskell" )
                        , ( "allow_live_comments" , Boolean False )
                        , ( "selftext_html"
                          , String
                              "&lt;!-- SC_OFF --&gt;&lt;div class=\\\"md\\\"&gt;&lt;p&gt;There seem to be some &lt;a href=\\\"https://www.reddit.com/r/haskell/comments/pen8s/anyone_else_used_write_yourself_a_scheme_in_48/\\\"&gt;posts&lt;/a&gt; about the book or the &lt;a href=\\\"https://wespiser.com/writings/wyas/00_overview.html\\\"&gt;Write You a Scheme V2.0&lt;/a&gt;, but I&amp;#39;m unsure how much Scheme I need to tackle this project.&lt;/p&gt;\\n\\n&lt;p&gt;I&amp;#39;ve thumbed through the (in)famous Learn You a Haskell, and implementing an interpreter sounds like a lot of fun, but perhaps I might not down this path if I have to spend the time to buckle down and learn some Scheme syntax too.&lt;/p&gt;\\n&lt;/div&gt;&lt;!-- SC_ON --&gt;"
                          )
                        , ( "likes" , Null )
                        , ( "suggested_sort" , Null )
                        , ( "banned_at_utc" , Null )
                        , ( "view_count" , Null )
                        , ( "archived" , Boolean False )
                        , ( "no_follow" , Boolean False )
                        , ( "is_crosspostable" , Boolean False )
                        , ( "pinned" , Boolean False )
                        , ( "over_18" , Boolean False )
                        , ( "all_awardings" , Array [] )
                        , ( "awarders" , Array [] )
                        , ( "media_only" , Boolean False )
                        , ( "can_gild" , Boolean False )
                        , ( "spoiler" , Boolean False )
                        , ( "locked" , Boolean False )
                        , ( "author_flair_text" , Null )
                        , ( "treatment_tags" , Array [] )
                        , ( "visited" , Boolean False )
                        , ( "removed_by" , Null )
                        , ( "num_reports" , Null )
                        , ( "distinguished" , Null )
                        , ( "subreddit_id" , String "t5_2qh36" )
                        , ( "mod_reason_by" , Null )
                        , ( "removal_reason" , Null )
                        , ( "link_flair_background_color" , String "" )
                        , ( "id" , String "gm3ia1" )
                        , ( "is_robot_indexable" , Boolean True )
                        , ( "report_reasons" , Null )
                        , ( "author" , String "0x2fwhc" )
                        , ( "discussion_type" , Null )
                        , ( "num_comments" , Number (5 % 1) )
                        , ( "send_replies" , Boolean False )
                        , ( "whitelist_status" , String "all_ads" )
                        , ( "contest_mode" , Boolean False )
                        , ( "mod_reports" , Array [] )
                        , ( "author_patreon_flair" , Boolean False )
                        , ( "author_flair_text_color" , Null )
                        , ( "permalink"
                          , String
                              "/r/haskell/comments/gm3ia1/how_much_scheme_needed_for_write_yourself_a/"
                          )
                        , ( "parent_whitelist_status" , String "all_ads" )
                        , ( "stickied" , Boolean False )
                        , ( "url"
                          , String
                              "https://old.reddit.com/r/haskell/comments/gm3ia1/how_much_scheme_needed_for_write_yourself_a/"
                          )
                        , ( "subreddit_subscribers" , Number (55194 % 1) )
                        , ( "created_utc" , Number (1589815557 % 1) )
                        , ( "num_crossposts" , Number (0 % 1) )
                        , ( "media" , Null )
                        , ( "is_video" , Boolean False )
                        ]
                    )
                  ]
              , Object
                  [ ( "kind" , String "t3" )
                  , ( "data"
                    , Object
                        [ ( "approved_at_utc" , Null )
                        , ( "subreddit" , String "haskell" )
                        , ( "selftext"
                          , String
                              "GHC has releases versions 8.4.x, and 8.6.x, but there are no 8.5.x releases. Why does GHC skip odd minor versions?"
                          )
                        , ( "author_fullname" , String "t2_2lv4dufx" )
                        , ( "saved" , Boolean False )
                        , ( "mod_reason_title" , Null )
                        , ( "gilded" , Number (0 % 1) )
                        , ( "clicked" , Boolean False )
                        , ( "title" , String "GHC versioning scheme" )
                        , ( "link_flair_richtext" , Array [] )
                        , ( "subreddit_name_prefixed" , String "r/haskell" )
                        , ( "hidden" , Boolean False )
                        , ( "pwls" , Number (6 % 1) )
                        , ( "link_flair_css_class" , Null )
                        , ( "downs" , Number (0 % 1) )
                        , ( "hide_score" , Boolean False )
                        , ( "name" , String "t3_gm6mm7" )
                        , ( "quarantine" , Boolean False )
                        , ( "link_flair_text_color" , String "dark" )
                        , ( "upvote_ratio" , Number (8196551321814303 % 9007199254740992) )
                        , ( "author_flair_background_color" , Null )
                        , ( "subreddit_type" , String "public" )
                        , ( "ups" , Number (8 % 1) )
                        , ( "total_awards_received" , Number (0 % 1) )
                        , ( "media_embed" , Object [] )
                        , ( "author_flair_template_id" , Null )
                        , ( "is_original_content" , Boolean False )
                        , ( "user_reports" , Array [] )
                        , ( "secure_media" , Null )
                        , ( "is_reddit_media_domain" , Boolean False )
                        , ( "is_meta" , Boolean False )
                        , ( "category" , Null )
                        , ( "secure_media_embed" , Object [] )
                        , ( "link_flair_text" , Null )
                        , ( "can_mod_post" , Boolean False )
                        , ( "score" , Number (8 % 1) )
                        , ( "approved_by" , Null )
                        , ( "author_premium" , Boolean False )
                        , ( "thumbnail" , String "" )
                        , ( "edited" , Boolean False )
                        , ( "author_flair_css_class" , Null )
                        , ( "author_flair_richtext" , Array [] )
                        , ( "gildings" , Object [] )
                        , ( "content_categories" , Null )
                        , ( "is_self" , Boolean True )
                        , ( "mod_note" , Null )
                        , ( "created" , Number (1589853843 % 1) )
                        , ( "link_flair_type" , String "text" )
                        , ( "wls" , Number (6 % 1) )
                        , ( "removed_by_category" , Null )
                        , ( "banned_by" , Null )
                        , ( "author_flair_type" , String "text" )
                        , ( "domain" , String "self.haskell" )
                        , ( "allow_live_comments" , Boolean False )
                        , ( "selftext_html"
                          , String
                              "&lt;!-- SC_OFF --&gt;&lt;div class=\\\"md\\\"&gt;&lt;p&gt;GHC has releases versions 8.4.x, and 8.6.x, but there are no 8.5.x releases. Why does GHC skip odd minor versions?&lt;/p&gt;\\n&lt;/div&gt;&lt;!-- SC_ON --&gt;"
                          )
                        , ( "likes" , Null )
                        , ( "suggested_sort" , Null )
                        , ( "banned_at_utc" , Null )
                        , ( "view_count" , Null )
                        , ( "archived" , Boolean False )
                        , ( "no_follow" , Boolean False )
                        , ( "is_crosspostable" , Boolean False )
                        , ( "pinned" , Boolean False )
                        , ( "over_18" , Boolean False )
                        , ( "all_awardings" , Array [] )
                        , ( "awarders" , Array [] )
                        , ( "media_only" , Boolean False )
                        , ( "can_gild" , Boolean False )
                        , ( "spoiler" , Boolean False )
                        , ( "locked" , Boolean False )
                        , ( "author_flair_text" , Null )
                        , ( "treatment_tags" , Array [] )
                        , ( "visited" , Boolean False )
                        , ( "removed_by" , Null )
                        , ( "num_reports" , Null )
                        , ( "distinguished" , Null )
                        , ( "subreddit_id" , String "t5_2qh36" )
                        , ( "mod_reason_by" , Null )
                        , ( "removal_reason" , Null )
                        , ( "link_flair_background_color" , String "" )
                        , ( "id" , String "gm6mm7" )
                        , ( "is_robot_indexable" , Boolean True )
                        , ( "report_reasons" , Null )
                        , ( "author" , String "NinjaPenguin54" )
                        , ( "discussion_type" , Null )
                        , ( "num_comments" , Number (6 % 1) )
                        , ( "send_replies" , Boolean True )
                        , ( "whitelist_status" , String "all_ads" )
                        , ( "contest_mode" , Boolean False )
                        , ( "mod_reports" , Array [] )
                        , ( "author_patreon_flair" , Boolean False )
                        , ( "author_flair_text_color" , Null )
                        , ( "permalink"
                          , String "/r/haskell/comments/gm6mm7/ghc_versioning_scheme/"
                          )
                        , ( "parent_whitelist_status" , String "all_ads" )
                        , ( "stickied" , Boolean False )
                        , ( "url"
                          , String
                              "https://old.reddit.com/r/haskell/comments/gm6mm7/ghc_versioning_scheme/"
                          )
                        , ( "subreddit_subscribers" , Number (55194 % 1) )
                        , ( "created_utc" , Number (1589825043 % 1) )
                        , ( "num_crossposts" , Number (0 % 1) )
                        , ( "media" , Null )
                        , ( "is_video" , Boolean False )
                        ]
                    )
                  ]
              , Object
                  [ ( "kind" , String "t3" )
                  , ( "data"
                    , Object
                        [ ( "approved_at_utc" , Null )
                        , ( "subreddit" , String "haskell" )
                        , ( "selftext"
                          , String
                              "Hello fellow Haskellers,\\n\\nI've spent last half year learning Haskell and managed to write my first real-world Haskell application. Now I have some ideas for Haskell libraries, that could be (hopefully) useful, but have zero experience designing library for Haskell (mainly from API perspective). Building library is clearly different than building CLI tool, as the main \\\"API\\\" of CLI tool is the command line interface, which is pretty restrictive, but library API should be more flexible to suit different styles and designs of end-user programs. Also if such library is badly designed from start, it's hard to completely change the API style as it breaks compatibility and causes troubles. So I'd like to ask you to share your experience on this topic, mainly following points:\\n\\n1. **handling exceptions** \\\\- I know, this is probably controversial topic, but I'd like to know whether there is any current consensus. Let's say that my library will provide IO operations that may fail because 1/ there is no result for the given input or 2/ there is some IO error (file doesn't exist, etc.). In my CLI tool, I used the approach summarized by u/snoyberg in [this blog post](https://www.fpcomplete.com/blog/2016/11/exceptions-best-practices-haskell), i.e. using `MonadThrow` with `MonadIO`, like `parseJsonFile :: (MonadThrow m, MonadIO m) =&gt; FilePath -&gt; m JSON`. But I'm wondering if this is good approach for library? Because the `MonadThrow` itself isn't really specific about the type of the error it can throw. Would it be better to use something as `MonadError` maybe?\\n2. **RIO** \\\\- In my CLI app I'm pretty happy with [RIO](https://hackage.haskell.org/package/rio), both as Prelude replacement and RIO Monad, but I guess it's not good idea to force end-users to use the RIO-style in library, right?\\n3. **language extensions** \\\\- GHC language extensions are pretty common to use nowadays, but are there any of them I should explicitly avoid using in libraries?\\n4. **overall architecture** \\\\- This is closely related to 1). Should I go full mtl for the library design, or maybe keep it simpler and use just some combination of things like `MonadIO`, `MonadThrow` or `MonadError`?\\n\\nI'll be grateful for any shared experience, comments, links to blog posts/book. Thanks a lot in advance."
                          )
                        , ( "author_fullname" , String "t2_kjucw" )
                        , ( "saved" , Boolean False )
                        , ( "mod_reason_title" , Null )
                        , ( "gilded" , Number (0 % 1) )
                        , ( "clicked" , Boolean False )
                        , ( "title"
                          , String "Designing Haskell library - best practices?"
                          )
                        , ( "link_flair_richtext" , Array [] )
                        , ( "subreddit_name_prefixed" , String "r/haskell" )
                        , ( "hidden" , Boolean False )
                        , ( "pwls" , Number (6 % 1) )
                        , ( "link_flair_css_class" , Null )
                        , ( "downs" , Number (0 % 1) )
                        , ( "hide_score" , Boolean False )
                        , ( "name" , String "t3_gm3v3g" )
                        , ( "quarantine" , Boolean False )
                        , ( "link_flair_text_color" , String "dark" )
                        , ( "upvote_ratio" , Number (8286623314361713 % 9007199254740992) )
                        , ( "author_flair_background_color" , Null )
                        , ( "subreddit_type" , String "public" )
                        , ( "ups" , Number (10 % 1) )
                        , ( "total_awards_received" , Number (0 % 1) )
                        , ( "media_embed" , Object [] )
                        , ( "author_flair_template_id" , Null )
                        , ( "is_original_content" , Boolean False )
                        , ( "user_reports" , Array [] )
                        , ( "secure_media" , Null )
                        , ( "is_reddit_media_domain" , Boolean False )
                        , ( "is_meta" , Boolean False )
                        , ( "category" , Null )
                        , ( "secure_media_embed" , Object [] )
                        , ( "link_flair_text" , Null )
                        , ( "can_mod_post" , Boolean False )
                        , ( "score" , Number (10 % 1) )
                        , ( "approved_by" , Null )
                        , ( "author_premium" , Boolean False )
                        , ( "thumbnail" , String "" )
                        , ( "edited" , Boolean False )
                        , ( "author_flair_css_class" , Null )
                        , ( "author_flair_richtext" , Array [] )
                        , ( "gildings" , Object [] )
                        , ( "content_categories" , Null )
                        , ( "is_self" , Boolean True )
                        , ( "mod_note" , Null )
                        , ( "created" , Number (1589845467 % 1) )
                        , ( "link_flair_type" , String "text" )
                        , ( "wls" , Number (6 % 1) )
                        , ( "removed_by_category" , Null )
                        , ( "banned_by" , Null )
                        , ( "author_flair_type" , String "text" )
                        , ( "domain" , String "self.haskell" )
                        , ( "allow_live_comments" , Boolean False )
                        , ( "selftext_html"
                          , String
                              "&lt;!-- SC_OFF --&gt;&lt;div class=\\\"md\\\"&gt;&lt;p&gt;Hello fellow Haskellers,&lt;/p&gt;\\n\\n&lt;p&gt;I&amp;#39;ve spent last half year learning Haskell and managed to write my first real-world Haskell application. Now I have some ideas for Haskell libraries, that could be (hopefully) useful, but have zero experience designing library for Haskell (mainly from API perspective). Building library is clearly different than building CLI tool, as the main &amp;quot;API&amp;quot; of CLI tool is the command line interface, which is pretty restrictive, but library API should be more flexible to suit different styles and designs of end-user programs. Also if such library is badly designed from start, it&amp;#39;s hard to completely change the API style as it breaks compatibility and causes troubles. So I&amp;#39;d like to ask you to share your experience on this topic, mainly following points:&lt;/p&gt;\\n\\n&lt;ol&gt;\\n&lt;li&gt;&lt;strong&gt;handling exceptions&lt;/strong&gt; - I know, this is probably controversial topic, but I&amp;#39;d like to know whether there is any current consensus. Let&amp;#39;s say that my library will provide IO operations that may fail because 1/ there is no result for the given input or 2/ there is some IO error (file doesn&amp;#39;t exist, etc.). In my CLI tool, I used the approach summarized by &lt;a href=\\\"/u/snoyberg\\\"&gt;u/snoyberg&lt;/a&gt; in &lt;a href=\\\"https://www.fpcomplete.com/blog/2016/11/exceptions-best-practices-haskell\\\"&gt;this blog post&lt;/a&gt;, i.e. using &lt;code&gt;MonadThrow&lt;/code&gt; with &lt;code&gt;MonadIO&lt;/code&gt;, like &lt;code&gt;parseJsonFile :: (MonadThrow m, MonadIO m) =&amp;gt; FilePath -&amp;gt; m JSON&lt;/code&gt;. But I&amp;#39;m wondering if this is good approach for library? Because the &lt;code&gt;MonadThrow&lt;/code&gt; itself isn&amp;#39;t really specific about the type of the error it can throw. Would it be better to use something as &lt;code&gt;MonadError&lt;/code&gt; maybe?&lt;/li&gt;\\n&lt;li&gt;&lt;strong&gt;RIO&lt;/strong&gt; - In my CLI app I&amp;#39;m pretty happy with &lt;a href=\\\"https://hackage.haskell.org/package/rio\\\"&gt;RIO&lt;/a&gt;, both as Prelude replacement and RIO Monad, but I guess it&amp;#39;s not good idea to force end-users to use the RIO-style in library, right?&lt;/li&gt;\\n&lt;li&gt;&lt;strong&gt;language extensions&lt;/strong&gt; - GHC language extensions are pretty common to use nowadays, but are there any of them I should explicitly avoid using in libraries?&lt;/li&gt;\\n&lt;li&gt;&lt;strong&gt;overall architecture&lt;/strong&gt; - This is closely related to 1). Should I go full mtl for the library design, or maybe keep it simpler and use just some combination of things like &lt;code&gt;MonadIO&lt;/code&gt;, &lt;code&gt;MonadThrow&lt;/code&gt; or &lt;code&gt;MonadError&lt;/code&gt;?&lt;/li&gt;\\n&lt;/ol&gt;\\n\\n&lt;p&gt;I&amp;#39;ll be grateful for any shared experience, comments, links to blog posts/book. Thanks a lot in advance.&lt;/p&gt;\\n&lt;/div&gt;&lt;!-- SC_ON --&gt;"
                          )
                        , ( "likes" , Null )
                        , ( "suggested_sort" , Null )
                        , ( "banned_at_utc" , Null )
                        , ( "view_count" , Null )
                        , ( "archived" , Boolean False )
                        , ( "no_follow" , Boolean False )
                        , ( "is_crosspostable" , Boolean False )
                        , ( "pinned" , Boolean False )
                        , ( "over_18" , Boolean False )
                        , ( "all_awardings" , Array [] )
                        , ( "awarders" , Array [] )
                        , ( "media_only" , Boolean False )
                        , ( "can_gild" , Boolean False )
                        , ( "spoiler" , Boolean False )
                        , ( "locked" , Boolean False )
                        , ( "author_flair_text" , Null )
                        , ( "treatment_tags" , Array [] )
                        , ( "visited" , Boolean False )
                        , ( "removed_by" , Null )
                        , ( "num_reports" , Null )
                        , ( "distinguished" , Null )
                        , ( "subreddit_id" , String "t5_2qh36" )
                        , ( "mod_reason_by" , Null )
                        , ( "removal_reason" , Null )
                        , ( "link_flair_background_color" , String "" )
                        , ( "id" , String "gm3v3g" )
                        , ( "is_robot_indexable" , Boolean True )
                        , ( "report_reasons" , Null )
                        , ( "author" , String "xwinus" )
                        , ( "discussion_type" , Null )
                        , ( "num_comments" , Number (5 % 1) )
                        , ( "send_replies" , Boolean True )
                        , ( "whitelist_status" , String "all_ads" )
                        , ( "contest_mode" , Boolean False )
                        , ( "mod_reports" , Array [] )
                        , ( "author_patreon_flair" , Boolean False )
                        , ( "author_flair_text_color" , Null )
                        , ( "permalink"
                          , String
                              "/r/haskell/comments/gm3v3g/designing_haskell_library_best_practices/"
                          )
                        , ( "parent_whitelist_status" , String "all_ads" )
                        , ( "stickied" , Boolean False )
                        , ( "url"
                          , String
                              "https://old.reddit.com/r/haskell/comments/gm3v3g/designing_haskell_library_best_practices/"
                          )
                        , ( "subreddit_subscribers" , Number (55194 % 1) )
                        , ( "created_utc" , Number (1589816667 % 1) )
                        , ( "num_crossposts" , Number (0 % 1) )
                        , ( "media" , Null )
                        , ( "is_video" , Boolean False )
                        ]
                    )
                  ]
              , Object
                  [ ( "kind" , String "t3" )
                  , ( "data"
                    , Object
                        [ ( "approved_at_utc" , Null )
                        , ( "subreddit" , String "haskell" )
                        , ( "selftext"
                          , String
                              "Un dictionnaire en Python peut contenir des donn\\u00e9es de toute sortes de type.\\n\\nDans ce nouveau chapitre, nous allons utiliser le syst\\u00e8me de type pour cr\\u00e9er des enregistrements \\u00ab extensibles \\u00bb, ce qui revient \\u00e0 appliquer des r\\u00e8gles de typage aux objets ad hoc des langages dynamiques.\\n\\nC'est un bon pr\\u00e9texte pour faire un retour sur plusieurs notions d\\u00e9j\\u00e0 abord\\u00e9es : les repr\\u00e9sentations canoniques, les Types Somme, Produit, existentiels, de rang n et les types de donn\\u00e9e alg\\u00e9briques g\\u00e9n\\u00e9ralis\\u00e9s.\\n\\nEn s'exer\\u00e7ant \\u00e0 leur usage, nous verrons aussi de nouvelles notions et pratiques, comme :\\n\\n* les types index\\u00e9s,\\n* les tandems de constructeurs de donn\\u00e9e dangereux rendus s\\u00fbr par des constructeurs intelligents,\\n* des \\u00e9l\\u00e9ments du module GHC.TypeLits et du paquet first-class-families,\\n* se servir de familles de types comme contrainte ou index sur un type Produit,\\n* les \\u00e9tiquettes surcharg\\u00e9es (extension OverloadedLabels) qui permettent de transformer `get (Key @\\\"example\\\") foo` en `get #example foo` (c'est aussi l'occasion de parler d'astuce de contrainte et d'en-t\\u00eate d\\u2019instance).\\n\\nFa\\u00eetes circuler l'info s'il vous pla\\u00eet, \\u00e7a me rend bien service.\\n\\nBonne r\\u00e9flexion !"
                          )
                        , ( "author_fullname" , String "t2_167bmq" )
                        , ( "saved" , Boolean False )
                        , ( "mod_reason_title" , Null )
                        , ( "gilded" , Number (0 % 1) )
                        , ( "clicked" , Boolean False )
                        , ( "title"
                          , String
                              "\\\"Penser en Types\\\" - Chapitre 11 (update in the translation of \\\"Thinking with Types\\\")"
                          )
                        , ( "link_flair_richtext" , Array [] )
                        , ( "subreddit_name_prefixed" , String "r/haskell" )
                        , ( "hidden" , Boolean False )
                        , ( "pwls" , Number (6 % 1) )
                        , ( "link_flair_css_class" , Null )
                        , ( "downs" , Number (0 % 1) )
                        , ( "hide_score" , Boolean False )
                        , ( "name" , String "t3_gm5nzd" )
                        , ( "quarantine" , Boolean False )
                        , ( "link_flair_text_color" , String "dark" )
                        , ( "upvote_ratio" , Number (1553741871442821 % 2251799813685248) )
                        , ( "author_flair_background_color" , Null )
                        , ( "subreddit_type" , String "public" )
                        , ( "ups" , Number (5 % 1) )
                        , ( "total_awards_received" , Number (0 % 1) )
                        , ( "media_embed" , Object [] )
                        , ( "author_flair_template_id" , Null )
                        , ( "is_original_content" , Boolean False )
                        , ( "user_reports" , Array [] )
                        , ( "secure_media" , Null )
                        , ( "is_reddit_media_domain" , Boolean False )
                        , ( "is_meta" , Boolean False )
                        , ( "category" , Null )
                        , ( "secure_media_embed" , Object [] )
                        , ( "link_flair_text" , Null )
                        , ( "can_mod_post" , Boolean False )
                        , ( "score" , Number (5 % 1) )
                        , ( "approved_by" , Null )
                        , ( "author_premium" , Boolean False )
                        , ( "thumbnail" , String "" )
                        , ( "edited" , Boolean False )
                        , ( "author_flair_css_class" , Null )
                        , ( "author_flair_richtext" , Array [] )
                        , ( "gildings" , Object [] )
                        , ( "content_categories" , Null )
                        , ( "is_self" , Boolean True )
                        , ( "mod_note" , Null )
                        , ( "created" , Number (1589850981 % 1) )
                        , ( "link_flair_type" , String "text" )
                        , ( "wls" , Number (6 % 1) )
                        , ( "removed_by_category" , Null )
                        , ( "banned_by" , Null )
                        , ( "author_flair_type" , String "text" )
                        , ( "domain" , String "self.haskell" )
                        , ( "allow_live_comments" , Boolean False )
                        , ( "selftext_html"
                          , String
                              "&lt;!-- SC_OFF --&gt;&lt;div class=\\\"md\\\"&gt;&lt;p&gt;Un dictionnaire en Python peut contenir des donn\\u00e9es de toute sortes de type.&lt;/p&gt;\\n\\n&lt;p&gt;Dans ce nouveau chapitre, nous allons utiliser le syst\\u00e8me de type pour cr\\u00e9er des enregistrements \\u00ab extensibles \\u00bb, ce qui revient \\u00e0 appliquer des r\\u00e8gles de typage aux objets ad hoc des langages dynamiques.&lt;/p&gt;\\n\\n&lt;p&gt;C&amp;#39;est un bon pr\\u00e9texte pour faire un retour sur plusieurs notions d\\u00e9j\\u00e0 abord\\u00e9es : les repr\\u00e9sentations canoniques, les Types Somme, Produit, existentiels, de rang n et les types de donn\\u00e9e alg\\u00e9briques g\\u00e9n\\u00e9ralis\\u00e9s.&lt;/p&gt;\\n\\n&lt;p&gt;En s&amp;#39;exer\\u00e7ant \\u00e0 leur usage, nous verrons aussi de nouvelles notions et pratiques, comme :&lt;/p&gt;\\n\\n&lt;ul&gt;\\n&lt;li&gt;les types index\\u00e9s,&lt;/li&gt;\\n&lt;li&gt;les tandems de constructeurs de donn\\u00e9e dangereux rendus s\\u00fbr par des constructeurs intelligents,&lt;/li&gt;\\n&lt;li&gt;des \\u00e9l\\u00e9ments du module GHC.TypeLits et du paquet first-class-families,&lt;/li&gt;\\n&lt;li&gt;se servir de familles de types comme contrainte ou index sur un type Produit,&lt;/li&gt;\\n&lt;li&gt;les \\u00e9tiquettes surcharg\\u00e9es (extension OverloadedLabels) qui permettent de transformer &lt;code&gt;get (Key @&amp;quot;example&amp;quot;) foo&lt;/code&gt; en &lt;code&gt;get #example foo&lt;/code&gt; (c&amp;#39;est aussi l&amp;#39;occasion de parler d&amp;#39;astuce de contrainte et d&amp;#39;en-t\\u00eate d\\u2019instance).&lt;/li&gt;\\n&lt;/ul&gt;\\n\\n&lt;p&gt;Fa\\u00eetes circuler l&amp;#39;info s&amp;#39;il vous pla\\u00eet, \\u00e7a me rend bien service.&lt;/p&gt;\\n\\n&lt;p&gt;Bonne r\\u00e9flexion !&lt;/p&gt;\\n&lt;/div&gt;&lt;!-- SC_ON --&gt;"
                          )
                        , ( "likes" , Null )
                        , ( "suggested_sort" , Null )
                        , ( "banned_at_utc" , Null )
                        , ( "view_count" , Null )
                        , ( "archived" , Boolean False )
                        , ( "no_follow" , Boolean False )
                        , ( "is_crosspostable" , Boolean False )
                        , ( "pinned" , Boolean False )
                        , ( "over_18" , Boolean False )
                        , ( "all_awardings" , Array [] )
                        , ( "awarders" , Array [] )
                        , ( "media_only" , Boolean False )
                        , ( "can_gild" , Boolean False )
                        , ( "spoiler" , Boolean False )
                        , ( "locked" , Boolean False )
                        , ( "author_flair_text" , Null )
                        , ( "treatment_tags" , Array [] )
                        , ( "visited" , Boolean False )
                        , ( "removed_by" , Null )
                        , ( "num_reports" , Null )
                        , ( "distinguished" , Null )
                        , ( "subreddit_id" , String "t5_2qh36" )
                        , ( "mod_reason_by" , Null )
                        , ( "removal_reason" , Null )
                        , ( "link_flair_background_color" , String "" )
                        , ( "id" , String "gm5nzd" )
                        , ( "is_robot_indexable" , Boolean True )
                        , ( "report_reasons" , Null )
                        , ( "author" , String "jhderaigniac" )
                        , ( "discussion_type" , Null )
                        , ( "num_comments" , Number (0 % 1) )
                        , ( "send_replies" , Boolean True )
                        , ( "whitelist_status" , String "all_ads" )
                        , ( "contest_mode" , Boolean False )
                        , ( "mod_reports" , Array [] )
                        , ( "author_patreon_flair" , Boolean False )
                        , ( "author_flair_text_color" , Null )
                        , ( "permalink"
                          , String
                              "/r/haskell/comments/gm5nzd/penser_en_types_chapitre_11_update_in_the/"
                          )
                        , ( "parent_whitelist_status" , String "all_ads" )
                        , ( "stickied" , Boolean False )
                        , ( "url"
                          , String
                              "https://old.reddit.com/r/haskell/comments/gm5nzd/penser_en_types_chapitre_11_update_in_the/"
                          )
                        , ( "subreddit_subscribers" , Number (55194 % 1) )
                        , ( "created_utc" , Number (1589822181 % 1) )
                        , ( "num_crossposts" , Number (0 % 1) )
                        , ( "media" , Null )
                        , ( "is_video" , Boolean False )
                        ]
                    )
                  ]
              , Object
                  [ ( "kind" , String "t3" )
                  , ( "data"
                    , Object
                        [ ( "approved_at_utc" , Null )
                        , ( "subreddit" , String "haskell" )
                        , ( "selftext"
                          , String
                              "Hello,\\n\\nI could not find the answer anywhere so I thought I might ask here. My package was included in Stackage sometime at the end of April, but it's still not in any LTS release even though there have been a couple of LTS version bumps since then. What is the policy here? Is there anything I should do? Thanks in advance"
                          )
                        , ( "author_fullname" , String "t2_3epm" )
                        , ( "saved" , Boolean False )
                        , ( "mod_reason_title" , Null )
                        , ( "gilded" , Number (0 % 1) )
                        , ( "clicked" , Boolean False )
                        , ( "title"
                          , String "When packages are promoted to LTS in Stackage?"
                          )
                        , ( "link_flair_richtext" , Array [] )
                        , ( "subreddit_name_prefixed" , String "r/haskell" )
                        , ( "hidden" , Boolean False )
                        , ( "pwls" , Number (6 % 1) )
                        , ( "link_flair_css_class" , Null )
                        , ( "downs" , Number (0 % 1) )
                        , ( "hide_score" , Boolean False )
                        , ( "name" , String "t3_gm2484" )
                        , ( "quarantine" , Boolean False )
                        , ( "link_flair_text_color" , String "dark" )
                        , ( "upvote_ratio" , Number (1 % 1) )
                        , ( "author_flair_background_color" , Null )
                        , ( "subreddit_type" , String "public" )
                        , ( "ups" , Number (6 % 1) )
                        , ( "total_awards_received" , Number (0 % 1) )
                        , ( "media_embed" , Object [] )
                        , ( "author_flair_template_id" , Null )
                        , ( "is_original_content" , Boolean False )
                        , ( "user_reports" , Array [] )
                        , ( "secure_media" , Null )
                        , ( "is_reddit_media_domain" , Boolean False )
                        , ( "is_meta" , Boolean False )
                        , ( "category" , Null )
                        , ( "secure_media_embed" , Object [] )
                        , ( "link_flair_text" , Null )
                        , ( "can_mod_post" , Boolean False )
                        , ( "score" , Number (6 % 1) )
                        , ( "approved_by" , Null )
                        , ( "author_premium" , Boolean False )
                        , ( "thumbnail" , String "" )
                        , ( "edited" , Boolean False )
                        , ( "author_flair_css_class" , Null )
                        , ( "author_flair_richtext" , Array [] )
                        , ( "gildings" , Object [] )
                        , ( "content_categories" , Null )
                        , ( "is_self" , Boolean True )
                        , ( "mod_note" , Null )
                        , ( "created" , Number (1589839723 % 1) )
                        , ( "link_flair_type" , String "text" )
                        , ( "wls" , Number (6 % 1) )
                        , ( "removed_by_category" , Null )
                        , ( "banned_by" , Null )
                        , ( "author_flair_type" , String "text" )
                        , ( "domain" , String "self.haskell" )
                        , ( "allow_live_comments" , Boolean False )
                        , ( "selftext_html"
                          , String
                              "&lt;!-- SC_OFF --&gt;&lt;div class=\\\"md\\\"&gt;&lt;p&gt;Hello,&lt;/p&gt;\\n\\n&lt;p&gt;I could not find the answer anywhere so I thought I might ask here. My package was included in Stackage sometime at the end of April, but it&amp;#39;s still not in any LTS release even though there have been a couple of LTS version bumps since then. What is the policy here? Is there anything I should do? Thanks in advance&lt;/p&gt;\\n&lt;/div&gt;&lt;!-- SC_ON --&gt;"
                          )
                        , ( "likes" , Null )
                        , ( "suggested_sort" , Null )
                        , ( "banned_at_utc" , Null )
                        , ( "view_count" , Null )
                        , ( "archived" , Boolean False )
                        , ( "no_follow" , Boolean False )
                        , ( "is_crosspostable" , Boolean False )
                        , ( "pinned" , Boolean False )
                        , ( "over_18" , Boolean False )
                        , ( "all_awardings" , Array [] )
                        , ( "awarders" , Array [] )
                        , ( "media_only" , Boolean False )
                        , ( "can_gild" , Boolean False )
                        , ( "spoiler" , Boolean False )
                        , ( "locked" , Boolean False )
                        , ( "author_flair_text" , Null )
                        , ( "treatment_tags" , Array [] )
                        , ( "visited" , Boolean False )
                        , ( "removed_by" , Null )
                        , ( "num_reports" , Null )
                        , ( "distinguished" , Null )
                        , ( "subreddit_id" , String "t5_2qh36" )
                        , ( "mod_reason_by" , Null )
                        , ( "removal_reason" , Null )
                        , ( "link_flair_background_color" , String "" )
                        , ( "id" , String "gm2484" )
                        , ( "is_robot_indexable" , Boolean True )
                        , ( "report_reasons" , Null )
                        , ( "author" , String "rzeznik" )
                        , ( "discussion_type" , Null )
                        , ( "num_comments" , Number (2 % 1) )
                        , ( "send_replies" , Boolean True )
                        , ( "whitelist_status" , String "all_ads" )
                        , ( "contest_mode" , Boolean False )
                        , ( "mod_reports" , Array [] )
                        , ( "author_patreon_flair" , Boolean False )
                        , ( "author_flair_text_color" , Null )
                        , ( "permalink"
                          , String
                              "/r/haskell/comments/gm2484/when_packages_are_promoted_to_lts_in_stackage/"
                          )
                        , ( "parent_whitelist_status" , String "all_ads" )
                        , ( "stickied" , Boolean False )
                        , ( "url"
                          , String
                              "https://old.reddit.com/r/haskell/comments/gm2484/when_packages_are_promoted_to_lts_in_stackage/"
                          )
                        , ( "subreddit_subscribers" , Number (55194 % 1) )
                        , ( "created_utc" , Number (1589810923 % 1) )
                        , ( "num_crossposts" , Number (0 % 1) )
                        , ( "media" , Null )
                        , ( "is_video" , Boolean False )
                        ]
                    )
                  ]
              , Object
                  [ ( "kind" , String "t3" )
                  , ( "data"
                    , Object
                        [ ( "approved_at_utc" , Null )
                        , ( "subreddit" , String "haskell" )
                        , ( "selftext" , String "" )
                        , ( "author_fullname" , String "t2_o5q8o" )
                        , ( "saved" , Boolean False )
                        , ( "mod_reason_title" , Null )
                        , ( "gilded" , Number (0 % 1) )
                        , ( "clicked" , Boolean False )
                        , ( "title"
                          , String
                              "[ANN] password-2.0: library for working with passwords and password hashes"
                          )
                        , ( "link_flair_richtext" , Array [] )
                        , ( "subreddit_name_prefixed" , String "r/haskell" )
                        , ( "hidden" , Boolean False )
                        , ( "pwls" , Number (6 % 1) )
                        , ( "link_flair_css_class" , Null )
                        , ( "downs" , Number (0 % 1) )
                        , ( "hide_score" , Boolean False )
                        , ( "name" , String "t3_glte2r" )
                        , ( "quarantine" , Boolean False )
                        , ( "link_flair_text_color" , String "dark" )
                        , ( "upvote_ratio" , Number (4278419646001971 % 4503599627370496) )
                        , ( "author_flair_background_color" , Null )
                        , ( "subreddit_type" , String "public" )
                        , ( "ups" , Number (45 % 1) )
                        , ( "total_awards_received" , Number (0 % 1) )
                        , ( "media_embed" , Object [] )
                        , ( "author_flair_template_id" , Null )
                        , ( "is_original_content" , Boolean False )
                        , ( "user_reports" , Array [] )
                        , ( "secure_media" , Null )
                        , ( "is_reddit_media_domain" , Boolean False )
                        , ( "is_meta" , Boolean False )
                        , ( "category" , Null )
                        , ( "secure_media_embed" , Object [] )
                        , ( "link_flair_text" , Null )
                        , ( "can_mod_post" , Boolean False )
                        , ( "score" , Number (45 % 1) )
                        , ( "approved_by" , Null )
                        , ( "author_premium" , Boolean False )
                        , ( "thumbnail" , String "" )
                        , ( "edited" , Boolean False )
                        , ( "author_flair_css_class" , Null )
                        , ( "author_flair_richtext" , Array [] )
                        , ( "gildings" , Object [] )
                        , ( "content_categories" , Null )
                        , ( "is_self" , Boolean False )
                        , ( "mod_note" , Null )
                        , ( "created" , Number (1589800022 % 1) )
                        , ( "link_flair_type" , String "text" )
                        , ( "wls" , Number (6 % 1) )
                        , ( "removed_by_category" , Null )
                        , ( "banned_by" , Null )
                        , ( "author_flair_type" , String "text" )
                        , ( "domain" , String "functor.tokyo" )
                        , ( "allow_live_comments" , Boolean False )
                        , ( "selftext_html" , Null )
                        , ( "likes" , Null )
                        , ( "suggested_sort" , Null )
                        , ( "banned_at_utc" , Null )
                        , ( "view_count" , Null )
                        , ( "archived" , Boolean False )
                        , ( "no_follow" , Boolean False )
                        , ( "is_crosspostable" , Boolean False )
                        , ( "pinned" , Boolean False )
                        , ( "over_18" , Boolean False )
                        , ( "all_awardings" , Array [] )
                        , ( "awarders" , Array [] )
                        , ( "media_only" , Boolean False )
                        , ( "can_gild" , Boolean False )
                        , ( "spoiler" , Boolean False )
                        , ( "locked" , Boolean False )
                        , ( "author_flair_text" , Null )
                        , ( "treatment_tags" , Array [] )
                        , ( "visited" , Boolean False )
                        , ( "removed_by" , Null )
                        , ( "num_reports" , Null )
                        , ( "distinguished" , Null )
                        , ( "subreddit_id" , String "t5_2qh36" )
                        , ( "mod_reason_by" , Null )
                        , ( "removal_reason" , Null )
                        , ( "link_flair_background_color" , String "" )
                        , ( "id" , String "glte2r" )
                        , ( "is_robot_indexable" , Boolean True )
                        , ( "report_reasons" , Null )
                        , ( "author" , String "cdep_illabout" )
                        , ( "discussion_type" , Null )
                        , ( "num_comments" , Number (0 % 1) )
                        , ( "send_replies" , Boolean True )
                        , ( "whitelist_status" , String "all_ads" )
                        , ( "contest_mode" , Boolean False )
                        , ( "mod_reports" , Array [] )
                        , ( "author_patreon_flair" , Boolean False )
                        , ( "author_flair_text_color" , Null )
                        , ( "permalink"
                          , String
                              "/r/haskell/comments/glte2r/ann_password20_library_for_working_with_passwords/"
                          )
                        , ( "parent_whitelist_status" , String "all_ads" )
                        , ( "stickied" , Boolean False )
                        , ( "url"
                          , String "https://functor.tokyo/blog/2020-05-18-password-2.0"
                          )
                        , ( "subreddit_subscribers" , Number (55194 % 1) )
                        , ( "created_utc" , Number (1589771222 % 1) )
                        , ( "num_crossposts" , Number (0 % 1) )
                        , ( "media" , Null )
                        , ( "is_video" , Boolean False )
                        ]
                    )
                  ]
              , Object
                  [ ( "kind" , String "t3" )
                  , ( "data"
                    , Object
                        [ ( "approved_at_utc" , Null )
                        , ( "subreddit" , String "haskell" )
                        , ( "selftext" , String "" )
                        , ( "author_fullname" , String "t2_137hg4" )
                        , ( "saved" , Boolean False )
                        , ( "mod_reason_title" , Null )
                        , ( "gilded" , Number (0 % 1) )
                        , ( "clicked" , Boolean False )
                        , ( "title" , String "Trade-Offs in Type Safety" )
                        , ( "link_flair_richtext" , Array [] )
                        , ( "subreddit_name_prefixed" , String "r/haskell" )
                        , ( "hidden" , Boolean False )
                        , ( "pwls" , Number (6 % 1) )
                        , ( "link_flair_css_class" , Null )
                        , ( "downs" , Number (0 % 1) )
                        , ( "hide_score" , Boolean False )
                        , ( "name" , String "t3_glzz0l" )
                        , ( "quarantine" , Boolean False )
                        , ( "link_flair_text_color" , String "dark" )
                        , ( "upvote_ratio" , Number (6124895493223875 % 9007199254740992) )
                        , ( "author_flair_background_color" , Null )
                        , ( "subreddit_type" , String "public" )
                        , ( "ups" , Number (7 % 1) )
                        , ( "total_awards_received" , Number (0 % 1) )
                        , ( "media_embed" , Object [] )
                        , ( "author_flair_template_id" , Null )
                        , ( "is_original_content" , Boolean False )
                        , ( "user_reports" , Array [] )
                        , ( "secure_media" , Null )
                        , ( "is_reddit_media_domain" , Boolean False )
                        , ( "is_meta" , Boolean False )
                        , ( "category" , Null )
                        , ( "secure_media_embed" , Object [] )
                        , ( "link_flair_text" , Null )
                        , ( "can_mod_post" , Boolean False )
                        , ( "score" , Number (7 % 1) )
                        , ( "approved_by" , Null )
                        , ( "author_premium" , Boolean False )
                        , ( "thumbnail" , String "" )
                        , ( "edited" , Boolean False )
                        , ( "author_flair_css_class" , Null )
                        , ( "author_flair_richtext" , Array [] )
                        , ( "gildings" , Object [] )
                        , ( "content_categories" , Null )
                        , ( "is_self" , Boolean False )
                        , ( "mod_note" , Null )
                        , ( "created" , Number (1589831325 % 1) )
                        , ( "link_flair_type" , String "text" )
                        , ( "wls" , Number (6 % 1) )
                        , ( "removed_by_category" , Null )
                        , ( "banned_by" , Null )
                        , ( "author_flair_type" , String "text" )
                        , ( "domain" , String "alpacaaa.net" )
                        , ( "allow_live_comments" , Boolean False )
                        , ( "selftext_html" , Null )
                        , ( "likes" , Null )
                        , ( "suggested_sort" , Null )
                        , ( "banned_at_utc" , Null )
                        , ( "view_count" , Null )
                        , ( "archived" , Boolean False )
                        , ( "no_follow" , Boolean False )
                        , ( "is_crosspostable" , Boolean False )
                        , ( "pinned" , Boolean False )
                        , ( "over_18" , Boolean False )
                        , ( "all_awardings" , Array [] )
                        , ( "awarders" , Array [] )
                        , ( "media_only" , Boolean False )
                        , ( "can_gild" , Boolean False )
                        , ( "spoiler" , Boolean False )
                        , ( "locked" , Boolean False )
                        , ( "author_flair_text" , Null )
                        , ( "treatment_tags" , Array [] )
                        , ( "visited" , Boolean False )
                        , ( "removed_by" , Null )
                        , ( "num_reports" , Null )
                        , ( "distinguished" , Null )
                        , ( "subreddit_id" , String "t5_2qh36" )
                        , ( "mod_reason_by" , Null )
                        , ( "removal_reason" , Null )
                        , ( "link_flair_background_color" , String "" )
                        , ( "id" , String "glzz0l" )
                        , ( "is_robot_indexable" , Boolean True )
                        , ( "report_reasons" , Null )
                        , ( "author" , String "_alpacaaa" )
                        , ( "discussion_type" , Null )
                        , ( "num_comments" , Number (27 % 1) )
                        , ( "send_replies" , Boolean True )
                        , ( "whitelist_status" , String "all_ads" )
                        , ( "contest_mode" , Boolean False )
                        , ( "mod_reports" , Array [] )
                        , ( "author_patreon_flair" , Boolean False )
                        , ( "author_flair_text_color" , Null )
                        , ( "permalink"
                          , String "/r/haskell/comments/glzz0l/tradeoffs_in_type_safety/"
                          )
                        , ( "parent_whitelist_status" , String "all_ads" )
                        , ( "stickied" , Boolean False )
                        , ( "url" , String "https://alpacaaa.net/type-safety/" )
                        , ( "subreddit_subscribers" , Number (55194 % 1) )
                        , ( "created_utc" , Number (1589802525 % 1) )
                        , ( "num_crossposts" , Number (0 % 1) )
                        , ( "media" , Null )
                        , ( "is_video" , Boolean False )
                        ]
                    )
                  ]
              , Object
                  [ ( "kind" , String "t3" )
                  , ( "data"
                    , Object
                        [ ( "approved_at_utc" , Null )
                        , ( "subreddit" , String "haskell" )
                        , ( "selftext"
                          , String
                              "The Chalmers Online Functional Programming Seminar Series is organized by the Chalmers Functional Programming Group, as a way to exploit the fact that so many of us in the FP community are already meeting and working online these days. Our aim is to bring the people in the FP community closer together, to educate and inspire, and to foster collaboration.\\n\\nThe seminars will take place every Monday (at 7am PDT / 10am EDT / 16:00 CEST) and are **live streamed through YouTube**, and questions are taken through **sli.do**.\\n\\nWe continue tomorrow with Benjamin Pierce; title \\\"Backtracking Generators for Random Testing\\\". All welcome!\\n\\nLink to program, including videos of previous talks:\\n\\nhttp://chalmersfp.org/"
                          )
                        , ( "author_fullname" , String "t2_9ork9" )
                        , ( "saved" , Boolean False )
                        , ( "mod_reason_title" , Null )
                        , ( "gilded" , Number (0 % 1) )
                        , ( "clicked" , Boolean False )
                        , ( "title"
                          , String
                              "Reminder: The Chalmers Online Functional Programming Seminar Series continues tomorrow (Monday) with a talk by Benjamin Pierce"
                          )
                        , ( "link_flair_richtext" , Array [] )
                        , ( "subreddit_name_prefixed" , String "r/haskell" )
                        , ( "hidden" , Boolean False )
                        , ( "pwls" , Number (6 % 1) )
                        , ( "link_flair_css_class" , Null )
                        , ( "downs" , Number (0 % 1) )
                        , ( "hide_score" , Boolean False )
                        , ( "name" , String "t3_gld45o" )
                        , ( "quarantine" , Boolean False )
                        , ( "link_flair_text_color" , String "dark" )
                        , ( "upvote_ratio" , Number (2206763817411543 % 2251799813685248) )
                        , ( "author_flair_background_color" , Null )
                        , ( "subreddit_type" , String "public" )
                        , ( "ups" , Number (87 % 1) )
                        , ( "total_awards_received" , Number (0 % 1) )
                        , ( "media_embed" , Object [] )
                        , ( "author_flair_template_id" , Null )
                        , ( "is_original_content" , Boolean False )
                        , ( "user_reports" , Array [] )
                        , ( "secure_media" , Null )
                        , ( "is_reddit_media_domain" , Boolean False )
                        , ( "is_meta" , Boolean False )
                        , ( "category" , Null )
                        , ( "secure_media_embed" , Object [] )
                        , ( "link_flair_text" , Null )
                        , ( "can_mod_post" , Boolean False )
                        , ( "score" , Number (87 % 1) )
                        , ( "approved_by" , Null )
                        , ( "author_premium" , Boolean False )
                        , ( "thumbnail" , String "" )
                        , ( "edited" , Number (1589711120 % 1) )
                        , ( "author_flair_css_class" , Null )
                        , ( "author_flair_richtext" , Array [] )
                        , ( "gildings" , Object [] )
                        , ( "content_categories" , Null )
                        , ( "is_self" , Boolean True )
                        , ( "mod_note" , Null )
                        , ( "created" , Number (1589739615 % 1) )
                        , ( "link_flair_type" , String "text" )
                        , ( "wls" , Number (6 % 1) )
                        , ( "removed_by_category" , Null )
                        , ( "banned_by" , Null )
                        , ( "author_flair_type" , String "text" )
                        , ( "domain" , String "self.haskell" )
                        , ( "allow_live_comments" , Boolean False )
                        , ( "selftext_html"
                          , String
                              "&lt;!-- SC_OFF --&gt;&lt;div class=\\\"md\\\"&gt;&lt;p&gt;The Chalmers Online Functional Programming Seminar Series is organized by the Chalmers Functional Programming Group, as a way to exploit the fact that so many of us in the FP community are already meeting and working online these days. Our aim is to bring the people in the FP community closer together, to educate and inspire, and to foster collaboration.&lt;/p&gt;\\n\\n&lt;p&gt;The seminars will take place every Monday (at 7am PDT / 10am EDT / 16:00 CEST) and are &lt;strong&gt;live streamed through YouTube&lt;/strong&gt;, and questions are taken through &lt;strong&gt;sli.do&lt;/strong&gt;.&lt;/p&gt;\\n\\n&lt;p&gt;We continue tomorrow with Benjamin Pierce; title &amp;quot;Backtracking Generators for Random Testing&amp;quot;. All welcome!&lt;/p&gt;\\n\\n&lt;p&gt;Link to program, including videos of previous talks:&lt;/p&gt;\\n\\n&lt;p&gt;&lt;a href=\\\"http://chalmersfp.org/\\\"&gt;http://chalmersfp.org/&lt;/a&gt;&lt;/p&gt;\\n&lt;/div&gt;&lt;!-- SC_ON --&gt;"
                          )
                        , ( "likes" , Null )
                        , ( "suggested_sort" , Null )
                        , ( "banned_at_utc" , Null )
                        , ( "view_count" , Null )
                        , ( "archived" , Boolean False )
                        , ( "no_follow" , Boolean False )
                        , ( "is_crosspostable" , Boolean False )
                        , ( "pinned" , Boolean False )
                        , ( "over_18" , Boolean False )
                        , ( "all_awardings" , Array [] )
                        , ( "awarders" , Array [] )
                        , ( "media_only" , Boolean False )
                        , ( "can_gild" , Boolean False )
                        , ( "spoiler" , Boolean False )
                        , ( "locked" , Boolean False )
                        , ( "author_flair_text" , Null )
                        , ( "treatment_tags" , Array [] )
                        , ( "visited" , Boolean False )
                        , ( "removed_by" , Null )
                        , ( "num_reports" , Null )
                        , ( "distinguished" , Null )
                        , ( "subreddit_id" , String "t5_2qh36" )
                        , ( "mod_reason_by" , Null )
                        , ( "removal_reason" , Null )
                        , ( "link_flair_background_color" , String "" )
                        , ( "id" , String "gld45o" )
                        , ( "is_robot_indexable" , Boolean True )
                        , ( "report_reasons" , Null )
                        , ( "author" , String "koenclaessen" )
                        , ( "discussion_type" , Null )
                        , ( "num_comments" , Number (4 % 1) )
                        , ( "send_replies" , Boolean True )
                        , ( "whitelist_status" , String "all_ads" )
                        , ( "contest_mode" , Boolean False )
                        , ( "mod_reports" , Array [] )
                        , ( "author_patreon_flair" , Boolean False )
                        , ( "author_flair_text_color" , Null )
                        , ( "permalink"
                          , String
                              "/r/haskell/comments/gld45o/reminder_the_chalmers_online_functional/"
                          )
                        , ( "parent_whitelist_status" , String "all_ads" )
                        , ( "stickied" , Boolean False )
                        , ( "url"
                          , String
                              "https://old.reddit.com/r/haskell/comments/gld45o/reminder_the_chalmers_online_functional/"
                          )
                        , ( "subreddit_subscribers" , Number (55194 % 1) )
                        , ( "created_utc" , Number (1589710815 % 1) )
                        , ( "num_crossposts" , Number (0 % 1) )
                        , ( "media" , Null )
                        , ( "is_video" , Boolean False )
                        ]
                    )
                  ]
              ]
          )
        , ( "after" , String "t3_gld45o" )
        , ( "before" , Null )
        ]
    )
  ]

References: