This repository contains the program that parses the survey results and produces the graphs and JSON/CSV files. You can see the results of the survey here: https://taylor.fausak.me/2022/11/18/haskell-survey-results/
Last active
November 19, 2022 16:24
-
-
Save tfausak/2689c8468148d2342378d779b17ee352 to your computer and use it in GitHub Desktop.
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
packages: . |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
module HW_Answer where | |
import qualified Data.Text as Text | |
import qualified Data.Vector as Vector | |
import qualified HW_Other as Other | |
data Answer | |
= Single (Vector.Vector Text.Text) | |
| Multi Other.Other (Vector.Vector Text.Text) | |
| Extension (Vector.Vector Text.Text) | |
| Free | |
deriving (Eq, Show) |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
module HW_Bag where | |
import qualified Data.Aeson as Aeson | |
import qualified Data.ByteString.Lazy as LazyByteString | |
import qualified Data.Csv as Csv | |
import qualified Data.Set as Set | |
newtype Bag a = Bag | |
{ unwrap :: Set.Set a | |
} | |
deriving (Eq, Show) | |
instance (Aeson.FromJSON a, Ord a) => Aeson.FromJSON (Bag a) where | |
parseJSON = fmap Bag . Aeson.parseJSON | |
instance Aeson.ToJSON a => Aeson.ToJSON (Bag a) where | |
toJSON = Aeson.toJSON . unwrap | |
instance Csv.ToField a => Csv.ToField (Bag a) where | |
toField = LazyByteString.toStrict . Csv.encode . pure . Csv.toRecord . Set.toList . unwrap | |
empty :: Bag a | |
empty = Bag Set.empty |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
module HW_Choice where | |
import qualified Data.Aeson as Aeson | |
import qualified Data.Bool as Bool | |
import qualified Data.Csv as Csv | |
import qualified Data.Text as Text | |
newtype Choice = Choice | |
{ unwrap :: Bool | |
} | |
deriving (Eq, Show) | |
instance Aeson.FromJSON Choice where | |
parseJSON = Aeson.withText "Choice" $ \x -> case Text.unpack x of | |
"no" -> pure $ Choice False | |
"yes" -> pure $ Choice True | |
_ -> fail "invalid choice" | |
instance Aeson.ToJSON Choice where | |
toJSON = Aeson.toJSON . unwrap | |
instance Csv.ToField Choice where | |
toField = Csv.toField . Bool.bool "false" "true" . unwrap |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
{-# LANGUAGE OverloadedStrings #-} | |
import qualified Control.Monad as Monad | |
import qualified Data.Aeson as Aeson | |
import qualified Data.Aeson.Encode.Pretty as Aeson | |
import qualified Data.Bool as Bool | |
import qualified Data.ByteString.Lazy as LazyByteString | |
import qualified Data.CaseInsensitive as CI | |
import qualified Data.Csv as Csv | |
import qualified Data.List as List | |
import qualified Data.Map as Map | |
import qualified Data.Maybe as Maybe | |
import qualified Data.Ord as Ord | |
import qualified Data.Set as Set | |
import qualified Data.Text as Text | |
import qualified Data.Time as Time | |
import qualified Data.Vector as Vector | |
import qualified HW_Answer as Answer | |
import qualified HW_Bag as Bag | |
import qualified HW_Choice as Choice | |
import qualified HW_Other as Other | |
import qualified HW_Question as Question | |
import qualified HW_Response as Response | |
import qualified HW_Section as Section | |
import qualified HW_Singleton as Singleton | |
import qualified HW_Survey as Survey | |
import qualified HW_Timestamp as Timestamp | |
import qualified Lucid | |
import qualified Numeric.Natural as Natural | |
import qualified System.Directory as Directory | |
import System.FilePath ((</>)) | |
import qualified Text.Printf as Printf | |
main :: IO () | |
main = do | |
let input = "input" :: FilePath | |
let output = "output" :: FilePath | |
putStrLn "Getting responses ..." | |
entries <- Directory.listDirectory input | |
responses <- fmap (Vector.fromList . Maybe.catMaybes) . Monad.forM entries $ \entry -> do | |
let path = input </> entry | |
putStrLn $ "- " <> path | |
contents <- LazyByteString.readFile path | |
case Aeson.eitherDecode contents of | |
Left problem -> do | |
putStrLn $ "ERROR: " <> problem | |
pure Nothing | |
Right response -> pure $ Just response | |
putStrLn "Generating JSON ..." | |
LazyByteString.writeFile (output </> "2022-state-of-haskell-survey-results.json") $ | |
Aeson.encodePretty responses | |
putStrLn "Generating CSV ..." | |
LazyByteString.writeFile (output </> "2022-state-of-haskell-survey-results.csv") | |
. Csv.encodeDefaultOrderedByName | |
$ Vector.toList responses | |
putStrLn "Generating HTML ..." | |
LazyByteString.writeFile (output </> "2022-state-of-haskell-survey-results.html") | |
. LazyByteString.concatMap (\x -> LazyByteString.pack $ if x == 0x3c then [0x0a, x] else [x]) | |
. Lucid.renderBS | |
$ makeHtml responses | |
putStrLn "Done!" | |
makeHtml :: Vector.Vector Response.Response -> Lucid.Html () | |
makeHtml responses = Lucid.doctypehtml_ $ do | |
Lucid.head_ $ do | |
Lucid.meta_ [Lucid.charset_ "utf-8"] | |
Lucid.title_ "2022 State of Haskell Survey Results" | |
Lucid.style_ $ | |
Text.unwords | |
[ ".row { position: relative; }", | |
".row:hover { background: #cbc9e2; }", | |
".bar { height: 100%; left: 0; max-width: 100%; position: absolute; top: 0; }", | |
".purple { background: #9e9ac8; }", | |
".blue { background: #67a9cf; }", | |
".red { background: #ef8a62; }", | |
".percent, .count, .choice { display: inline-block; position: relative; }", | |
".percent, .count { text-align: right; width: 3em; }", | |
".choice { padding-left: 1em; }" | |
] | |
Lucid.body_ $ do | |
Lucid.h1_ "2022 State of Haskell Survey Results" | |
Lucid.ol_ . Monad.forM_ Survey.sections $ \section -> Lucid.li_ $ do | |
Lucid.a_ [Lucid.href_ $ "#" <> Section.anchor section] | |
. Lucid.toHtml | |
$ Section.title section | |
Lucid.ol_ . Monad.forM_ (Section.questions section) $ \question -> | |
Lucid.li_ | |
. Lucid.a_ [Lucid.href_ $ "#" <> Section.anchor section <> Question.anchor question] | |
. Lucid.toHtml | |
$ Question.prompt question | |
Monad.forM_ Survey.sections $ \section -> do | |
Lucid.h2_ [Lucid.id_ $ Section.anchor section] | |
. Lucid.toHtml | |
$ Section.title section | |
Monad.forM_ (Section.questions section) $ \question -> do | |
Lucid.h3_ [Lucid.id_ $ Section.anchor section <> Question.anchor question] | |
. Lucid.toHtml | |
$ Question.prompt question | |
let s = Section.index section | |
q = Question.index question | |
case Question.answer question of | |
Answer.Single choices -> do | |
Lucid.p_ "Optional. Single select." | |
makeSingleChart (getSingle s q) choices responses | |
Answer.Multi other choices -> do | |
Lucid.p_ "Optional. Multi select." | |
makeMultiChart other (getMulti s q) choices responses | |
Answer.Extension extensions -> do | |
Lucid.p_ "Optional. Multi select." | |
makeExtensionChart (getExtension s q) extensions responses | |
Answer.Free -> Lucid.p_ "Optional. Free response answers were collected but not analyzed." | |
makeSingleChart :: | |
(Response.Response -> Maybe (Singleton.Singleton Text.Text)) -> | |
Vector.Vector Text.Text -> | |
Vector.Vector Response.Response -> | |
Lucid.Html () | |
makeSingleChart f = | |
makeChart Other.Forbid $ | |
maybe Set.empty (Set.singleton . Singleton.unwrap) | |
. f | |
getSingle :: | |
Natural.Natural -> | |
Natural.Natural -> | |
Response.Response -> | |
Maybe (Singleton.Singleton Text.Text) | |
getSingle s q = case (s, q) of | |
(0, 1) -> Response.s0q1 | |
(0, 2) -> Response.s0q2 | |
(0, 4) -> Response.s0q4 | |
(0, 5) -> Response.s0q5 | |
(0, 6) -> Response.s0q6 | |
(0, 8) -> Response.s0q8 | |
(1, 0) -> Response.s1q0 | |
(1, 1) -> Response.s1q1 | |
(2, 2) -> Response.s2q2 | |
(2, 6) -> Response.s2q6 | |
(6, 0) -> Response.s6q0 | |
(6, 1) -> Response.s6q1 | |
(6, 2) -> Response.s6q2 | |
(6, 3) -> Response.s6q3 | |
(6, 4) -> Response.s6q4 | |
(6, 5) -> Response.s6q5 | |
(6, 6) -> Response.s6q6 | |
(6, 7) -> Response.s6q7 | |
(6, 8) -> Response.s6q8 | |
(6, 9) -> Response.s6q9 | |
(6, 10) -> Response.s6q10 | |
(6, 11) -> Response.s6q11 | |
(6, 12) -> Response.s6q12 | |
(6, 13) -> Response.s6q13 | |
(6, 14) -> Response.s6q14 | |
(6, 15) -> Response.s6q15 | |
(6, 16) -> Response.s6q16 | |
(6, 17) -> Response.s6q17 | |
(6, 18) -> Response.s6q18 | |
(6, 19) -> Response.s6q19 | |
(6, 20) -> Response.s6q20 | |
(6, 21) -> Response.s6q21 | |
(6, 22) -> Response.s6q22 | |
(6, 23) -> Response.s6q23 | |
(7, 0) -> Response.s7q0 | |
(7, 2) -> Response.s7q2 | |
(7, 3) -> Response.s7q3 | |
(7, 4) -> Response.s7q4 | |
(7, 5) -> Response.s7q5 | |
(7, 6) -> Response.s7q6 | |
(7, 7) -> Response.s7q7 | |
(7, 8) -> Response.s7q8 | |
(7, 9) -> Response.s7q9 | |
(7, 10) -> Response.s7q10 | |
(9, 0) -> Response.s9q0 | |
(9, 1) -> Response.s9q1 | |
(10, 0) -> Just . Singleton.Singleton . Text.pack . Time.formatTime Time.defaultTimeLocale "%Y-%m-%d" . Timestamp.unwrap . Singleton.unwrap . Response.finishedAt | |
(10, 1) -> Just . Singleton.Singleton . Bool.bool "No" "Yes" . Choice.unwrap . Response.s0q0 | |
_ -> error $ "getSingle " <> show s <> " " <> show q | |
makeMultiChart :: | |
Other.Other -> | |
(Response.Response -> Bag.Bag Text.Text) -> | |
Vector.Vector Text.Text -> | |
Vector.Vector Response.Response -> | |
Lucid.Html () | |
makeMultiChart other f = makeChart other $ Bag.unwrap . f | |
getMulti :: | |
Natural.Natural -> | |
Natural.Natural -> | |
Response.Response -> | |
Bag.Bag Text.Text | |
getMulti s q = case (s, q) of | |
(0, 3) -> Response.s0q3 | |
(0, 7) -> Response.s0q7 | |
(0, 9) -> Response.s0q9 | |
(0, 10) -> Response.s0q10 | |
(0, 11) -> Response.s0q11 | |
(0, 12) -> Response.s0q12 | |
(1, 2) -> Response.s1q2 | |
(1, 3) -> Response.s1q3 | |
(2, 0) -> Response.s2q0 | |
(2, 1) -> Response.s2q1 | |
(2, 3) -> Response.s2q3 | |
(2, 4) -> Response.s2q4 | |
(3, 0) -> Response.s3q0 | |
(3, 1) -> Response.s3q1 | |
(3, 2) -> Response.s3q2 | |
(3, 3) -> Response.s3q3 | |
(3, 4) -> Response.s3q4 | |
(3, 5) -> Response.s3q5 | |
(3, 6) -> Response.s3q6 | |
(4, 0) -> Response.s4q0 | |
(4, 1) -> Response.s4q1 | |
(5, 0) -> Response.s5q0 | |
(5, 1) -> Response.s5q1 | |
(7, 1) -> Response.s7q1 | |
(8, 0) -> Response.s8q0 | |
(8, 1) -> Response.s8q1 | |
_ -> error $ "getMulti " <> show s <> " " <> show q | |
makeExtensionChart :: | |
(Int -> Response.Response -> Maybe (Singleton.Singleton Choice.Choice)) -> | |
Vector.Vector Text.Text -> | |
Vector.Vector Response.Response -> | |
Lucid.Html () | |
makeExtensionChart f extensions responses = do | |
let total = fromIntegral $ Vector.length responses :: Double | |
xs = | |
List.sortOn (Ord.Down . fst . snd) | |
. Map.toList | |
. fmap ((\m -> (Map.findWithDefault 0 True m, Map.findWithDefault 0 False m)) . frequencies) | |
. Map.unionsWith (<>) | |
. fmap | |
( \response -> | |
Map.fromList | |
. fmap | |
( \(index, extension) -> | |
( extension, | |
maybe [] (pure . Choice.unwrap . Singleton.unwrap) $ f index response | |
) | |
) | |
. Vector.toList | |
$ Vector.indexed extensions | |
) | |
$ Vector.toList responses | |
Lucid.div_ [Lucid.class_ "answer"] | |
. Monad.forM_ xs | |
$ \(extension, (pro, con)) -> Lucid.div_ [Lucid.class_ "row"] $ do | |
let proPct = 100 * fromIntegral pro / total | |
conPct = 100 * fromIntegral con / total | |
Lucid.div_ [Lucid.class_ "bar blue", Lucid.style_ . Text.pack $ Printf.printf "width: %.2f%%;" proPct] mempty | |
Lucid.div_ [Lucid.class_ "bar red", Lucid.style_ . Text.pack $ Printf.printf "left: auto; right: 0; width: %.2f%%;" conPct] mempty | |
Lucid.div_ [Lucid.class_ "percent"] . Lucid.toHtml $ "+" <> show (round proPct :: Int) <> "%" | |
Lucid.div_ [Lucid.class_ "percent"] . Lucid.toHtml $ "-" <> show (round conPct :: Int) <> "%" | |
Lucid.div_ [Lucid.class_ "count"] . Lucid.toHtml $ "+" <> show pro | |
Lucid.div_ [Lucid.class_ "count"] . Lucid.toHtml $ "-" <> show con | |
Lucid.div_ [Lucid.class_ "choice"] $ Lucid.toHtml extension | |
getExtension :: | |
Natural.Natural -> | |
Natural.Natural -> | |
Int -> | |
Response.Response -> | |
Maybe (Singleton.Singleton Choice.Choice) | |
getExtension s q = case (s, q) of | |
(2, 5) -> \c -> case c of | |
0 -> Response.s2q5c0 | |
1 -> Response.s2q5c1 | |
2 -> Response.s2q5c2 | |
3 -> Response.s2q5c3 | |
4 -> Response.s2q5c4 | |
5 -> Response.s2q5c5 | |
6 -> Response.s2q5c6 | |
7 -> Response.s2q5c7 | |
8 -> Response.s2q5c8 | |
9 -> Response.s2q5c9 | |
10 -> Response.s2q5c10 | |
11 -> Response.s2q5c11 | |
12 -> Response.s2q5c12 | |
13 -> Response.s2q5c13 | |
14 -> Response.s2q5c14 | |
15 -> Response.s2q5c15 | |
16 -> Response.s2q5c16 | |
17 -> Response.s2q5c17 | |
18 -> Response.s2q5c18 | |
19 -> Response.s2q5c19 | |
20 -> Response.s2q5c20 | |
21 -> Response.s2q5c21 | |
22 -> Response.s2q5c22 | |
23 -> Response.s2q5c23 | |
24 -> Response.s2q5c24 | |
25 -> Response.s2q5c25 | |
26 -> Response.s2q5c26 | |
27 -> Response.s2q5c27 | |
28 -> Response.s2q5c28 | |
29 -> Response.s2q5c29 | |
30 -> Response.s2q5c30 | |
31 -> Response.s2q5c31 | |
32 -> Response.s2q5c32 | |
33 -> Response.s2q5c33 | |
34 -> Response.s2q5c34 | |
35 -> Response.s2q5c35 | |
36 -> Response.s2q5c36 | |
37 -> Response.s2q5c37 | |
38 -> Response.s2q5c38 | |
39 -> Response.s2q5c39 | |
40 -> Response.s2q5c40 | |
41 -> Response.s2q5c41 | |
42 -> Response.s2q5c42 | |
43 -> Response.s2q5c43 | |
44 -> Response.s2q5c44 | |
45 -> Response.s2q5c45 | |
46 -> Response.s2q5c46 | |
47 -> Response.s2q5c47 | |
48 -> Response.s2q5c48 | |
49 -> Response.s2q5c49 | |
50 -> Response.s2q5c50 | |
51 -> Response.s2q5c51 | |
52 -> Response.s2q5c52 | |
53 -> Response.s2q5c53 | |
54 -> Response.s2q5c54 | |
55 -> Response.s2q5c55 | |
56 -> Response.s2q5c56 | |
57 -> Response.s2q5c57 | |
58 -> Response.s2q5c58 | |
59 -> Response.s2q5c59 | |
60 -> Response.s2q5c60 | |
61 -> Response.s2q5c61 | |
62 -> Response.s2q5c62 | |
63 -> Response.s2q5c63 | |
64 -> Response.s2q5c64 | |
65 -> Response.s2q5c65 | |
66 -> Response.s2q5c66 | |
67 -> Response.s2q5c67 | |
68 -> Response.s2q5c68 | |
69 -> Response.s2q5c69 | |
70 -> Response.s2q5c70 | |
71 -> Response.s2q5c71 | |
72 -> Response.s2q5c72 | |
73 -> Response.s2q5c73 | |
74 -> Response.s2q5c74 | |
75 -> Response.s2q5c75 | |
76 -> Response.s2q5c76 | |
77 -> Response.s2q5c77 | |
78 -> Response.s2q5c78 | |
79 -> Response.s2q5c79 | |
80 -> Response.s2q5c80 | |
81 -> Response.s2q5c81 | |
82 -> Response.s2q5c82 | |
83 -> Response.s2q5c83 | |
84 -> Response.s2q5c84 | |
85 -> Response.s2q5c85 | |
86 -> Response.s2q5c86 | |
87 -> Response.s2q5c87 | |
88 -> Response.s2q5c88 | |
89 -> Response.s2q5c89 | |
90 -> Response.s2q5c90 | |
91 -> Response.s2q5c91 | |
92 -> Response.s2q5c92 | |
93 -> Response.s2q5c93 | |
94 -> Response.s2q5c94 | |
95 -> Response.s2q5c95 | |
96 -> Response.s2q5c96 | |
97 -> Response.s2q5c97 | |
98 -> Response.s2q5c98 | |
99 -> Response.s2q5c99 | |
100 -> Response.s2q5c100 | |
101 -> Response.s2q5c101 | |
102 -> Response.s2q5c102 | |
103 -> Response.s2q5c103 | |
104 -> Response.s2q5c104 | |
105 -> Response.s2q5c105 | |
106 -> Response.s2q5c106 | |
107 -> Response.s2q5c107 | |
108 -> Response.s2q5c108 | |
109 -> Response.s2q5c109 | |
110 -> Response.s2q5c110 | |
111 -> Response.s2q5c111 | |
112 -> Response.s2q5c112 | |
_ -> error $ "getExtension " <> show s <> " " <> show q <> " " <> show c | |
_ -> error $ "getExtension " <> show s <> " " <> show q | |
makeChart :: | |
Other.Other -> | |
(Response.Response -> Set.Set Text.Text) -> | |
Vector.Vector Text.Text -> | |
Vector.Vector Response.Response -> | |
Lucid.Html () | |
makeChart other f choices responses = do | |
let total = Vector.length responses | |
xs = frequencies . fmap normalize . concatMap (Set.toList . f) $ Vector.toList responses | |
choiceList = normalize <$> Vector.toList choices | |
leftovers = Map.withoutKeys xs . Set.fromList $ "n/a" : choiceList | |
counts = | |
fmap (\c -> (c, Map.findWithDefault 0 c xs)) choiceList | |
<> case other of | |
Other.Allow -> [("Other", sum $ Map.elems leftovers)] | |
Other.Forbid -> if Map.null leftovers then [] else error $ show leftovers | |
Lucid.div_ [Lucid.class_ "answer"] | |
. Monad.forM_ counts | |
$ \(choice, count) -> Lucid.div_ [Lucid.class_ "row"] $ do | |
let percent = 100 * fromIntegral count / fromIntegral total :: Double | |
Lucid.div_ [Lucid.class_ "bar purple", Lucid.style_ . Text.pack $ Printf.printf "width: %.2f%%;" percent] mempty | |
Lucid.div_ [Lucid.class_ "percent"] . Lucid.toHtml $ show (round percent :: Int) <> "%" | |
Lucid.div_ [Lucid.class_ "count"] . Lucid.toHtml $ show count | |
Lucid.div_ [Lucid.class_ "choice"] . Lucid.toHtml $ CI.original choice | |
normalize :: Text.Text -> CI.CI Text.Text | |
normalize = CI.mk . Text.unwords . Text.words | |
{- hlint ignore frequencies "Use tuple-section" -} | |
frequencies :: Ord a => [a] -> Map.Map a Int | |
frequencies = Map.fromListWith (+) . fmap (flip (,) 1) |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
module HW_Other where | |
data Other | |
= Allow | |
| Forbid | |
deriving (Eq, Show) |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
module HW_Question where | |
import qualified Data.Text as Text | |
import qualified HW_Answer as Answer | |
import qualified Numeric.Natural as Natural | |
data Question = Question | |
{ index :: Natural.Natural, | |
prompt :: Text.Text, | |
answer :: Answer.Answer | |
} | |
deriving (Eq, Show) | |
anchor :: Question -> Text.Text | |
anchor question = Text.pack $ "q" <> show (index question) |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
{-# LANGUAGE NamedFieldPuns #-} | |
module HW_Response where | |
import qualified Data.Aeson as Aeson | |
import qualified Data.Aeson.Key as Key | |
import qualified Data.Aeson.Types as Aeson | |
import qualified Data.Char as Char | |
import qualified Data.Csv as Csv | |
import qualified Data.Text as Text | |
import qualified Data.Text.Encoding as Text | |
import qualified Data.Vector as Vector | |
import qualified HW_Bag as Bag | |
import qualified HW_Choice as Choice | |
import qualified HW_Singleton as Singleton | |
import qualified HW_Timestamp as Timestamp | |
data Response = Response | |
{ startedAt :: Singleton.Singleton Timestamp.Timestamp, | |
finishedAt :: Singleton.Singleton Timestamp.Timestamp, | |
-- | What is your email address? | |
s0q0 :: Choice.Choice, | |
-- | Do you use Haskell? | |
s0q1 :: Maybe (Singleton.Singleton Text.Text), | |
-- | If you stopped using Haskell, how long did you use it before you stopped? | |
s0q2 :: Maybe (Singleton.Singleton Text.Text), | |
-- | If you do not use Haskell, why not? | |
s0q3 :: Bag.Bag Text.Text, | |
-- | How many years have you been using Haskell? | |
s0q4 :: Maybe (Singleton.Singleton Text.Text), | |
-- | How frequently do you use Haskell? | |
s0q5 :: Maybe (Singleton.Singleton Text.Text), | |
-- | How would you rate your proficiency in Haskell? | |
s0q6 :: Maybe (Singleton.Singleton Text.Text), | |
-- | Where do you use Haskell? | |
s0q7 :: Bag.Bag Text.Text, | |
-- | Do you use Haskell at work? | |
s0q8 :: Maybe (Singleton.Singleton Text.Text), | |
-- | If you do not use Haskell at work, why not? | |
s0q9 :: Bag.Bag Text.Text, | |
-- | Which programming languages other than Haskell are you fluent in? | |
s0q10 :: Bag.Bag Text.Text, | |
-- | Which types of software do you develop with Haskell? | |
s0q11 :: Bag.Bag Text.Text, | |
-- | Which industries do you use Haskell in? | |
s0q12 :: Bag.Bag Text.Text, | |
-- | How many Haskell projects do you contribute to? | |
s1q0 :: Maybe (Singleton.Singleton Text.Text), | |
-- | What is the total size of all the Haskell projects you contribute to? | |
s1q1 :: Maybe (Singleton.Singleton Text.Text), | |
-- | Which platforms do you develop Haskell on? | |
s1q2 :: Bag.Bag Text.Text, | |
-- | Which platforms do you target? | |
s1q3 :: Bag.Bag Text.Text, | |
-- | Which Haskell compilers do you use? | |
s2q0 :: Bag.Bag Text.Text, | |
-- | Which installation methods do you use for your Haskell compiler? | |
s2q1 :: Bag.Bag Text.Text, | |
-- | Has upgrading your Haskell compiler broken your code in the last year? | |
s2q2 :: Maybe (Singleton.Singleton Text.Text), | |
-- | How has upgrading your Haskell compiler broken your code in the last year? | |
s2q3 :: Bag.Bag Text.Text, | |
-- | Which versions of GHC do you use? | |
s2q4 :: Bag.Bag Text.Text, | |
-- | AllowAmbiguousTypes | |
s2q5c0 :: Maybe (Singleton.Singleton Choice.Choice), | |
-- | ApplicativeDo | |
s2q5c1 :: Maybe (Singleton.Singleton Choice.Choice), | |
-- | Arrows | |
s2q5c2 :: Maybe (Singleton.Singleton Choice.Choice), | |
-- | BangPatterns | |
s2q5c3 :: Maybe (Singleton.Singleton Choice.Choice), | |
-- | BinaryLiterals | |
s2q5c4 :: Maybe (Singleton.Singleton Choice.Choice), | |
-- | BlockArguments | |
s2q5c5 :: Maybe (Singleton.Singleton Choice.Choice), | |
-- | CApiFFI | |
s2q5c6 :: Maybe (Singleton.Singleton Choice.Choice), | |
-- | ConstrainedClassMethods | |
s2q5c7 :: Maybe (Singleton.Singleton Choice.Choice), | |
-- | ConstraintKinds | |
s2q5c8 :: Maybe (Singleton.Singleton Choice.Choice), | |
-- | Cpp | |
s2q5c9 :: Maybe (Singleton.Singleton Choice.Choice), | |
-- | DataKinds | |
s2q5c10 :: Maybe (Singleton.Singleton Choice.Choice), | |
-- | DatatypeContexts | |
s2q5c11 :: Maybe (Singleton.Singleton Choice.Choice), | |
-- | DefaultSignatures | |
s2q5c12 :: Maybe (Singleton.Singleton Choice.Choice), | |
-- | DeriveAnyClass | |
s2q5c13 :: Maybe (Singleton.Singleton Choice.Choice), | |
-- | DeriveDataTypeable | |
s2q5c14 :: Maybe (Singleton.Singleton Choice.Choice), | |
-- | DeriveFoldable | |
s2q5c15 :: Maybe (Singleton.Singleton Choice.Choice), | |
-- | DeriveFunctor | |
s2q5c16 :: Maybe (Singleton.Singleton Choice.Choice), | |
-- | DeriveGeneric | |
s2q5c17 :: Maybe (Singleton.Singleton Choice.Choice), | |
-- | DeriveLift | |
s2q5c18 :: Maybe (Singleton.Singleton Choice.Choice), | |
-- | DeriveTraversable | |
s2q5c19 :: Maybe (Singleton.Singleton Choice.Choice), | |
-- | DerivingStrategies | |
s2q5c20 :: Maybe (Singleton.Singleton Choice.Choice), | |
-- | DerivingVia | |
s2q5c21 :: Maybe (Singleton.Singleton Choice.Choice), | |
-- | DisambiguateRecordFields | |
s2q5c22 :: Maybe (Singleton.Singleton Choice.Choice), | |
-- | DuplicateRecordFields | |
s2q5c23 :: Maybe (Singleton.Singleton Choice.Choice), | |
-- | EmptyCase | |
s2q5c24 :: Maybe (Singleton.Singleton Choice.Choice), | |
-- | ExistentialQuantification | |
s2q5c25 :: Maybe (Singleton.Singleton Choice.Choice), | |
-- | ExplicitForAll | |
s2q5c26 :: Maybe (Singleton.Singleton Choice.Choice), | |
-- | ExplicitNamespaces | |
s2q5c27 :: Maybe (Singleton.Singleton Choice.Choice), | |
-- | ExtendedDefaultRules | |
s2q5c28 :: Maybe (Singleton.Singleton Choice.Choice), | |
-- | FlexibleContexts | |
s2q5c29 :: Maybe (Singleton.Singleton Choice.Choice), | |
-- | FlexibleInstances | |
s2q5c30 :: Maybe (Singleton.Singleton Choice.Choice), | |
-- | ForeignFunctionInterface | |
s2q5c31 :: Maybe (Singleton.Singleton Choice.Choice), | |
-- | FunctionalDependencies | |
s2q5c32 :: Maybe (Singleton.Singleton Choice.Choice), | |
-- | GADTs | |
s2q5c33 :: Maybe (Singleton.Singleton Choice.Choice), | |
-- | GADTSyntax | |
s2q5c34 :: Maybe (Singleton.Singleton Choice.Choice), | |
-- | GeneralizedNewtypeDeriving | |
s2q5c35 :: Maybe (Singleton.Singleton Choice.Choice), | |
-- | HexFloatLiterals | |
s2q5c36 :: Maybe (Singleton.Singleton Choice.Choice), | |
-- | ImplicitParams | |
s2q5c37 :: Maybe (Singleton.Singleton Choice.Choice), | |
-- | ImportQualifiedPost | |
s2q5c38 :: Maybe (Singleton.Singleton Choice.Choice), | |
-- | ImpredicativeTypes | |
s2q5c39 :: Maybe (Singleton.Singleton Choice.Choice), | |
-- | IncoherentInstances | |
s2q5c40 :: Maybe (Singleton.Singleton Choice.Choice), | |
-- | InstanceSigs | |
s2q5c41 :: Maybe (Singleton.Singleton Choice.Choice), | |
-- | InterruptibleFFI | |
s2q5c42 :: Maybe (Singleton.Singleton Choice.Choice), | |
-- | KindSignatures | |
s2q5c43 :: Maybe (Singleton.Singleton Choice.Choice), | |
-- | LambdaCase | |
s2q5c44 :: Maybe (Singleton.Singleton Choice.Choice), | |
-- | LiberalTypeSynonyms | |
s2q5c45 :: Maybe (Singleton.Singleton Choice.Choice), | |
-- | LinearTypes | |
s2q5c46 :: Maybe (Singleton.Singleton Choice.Choice), | |
-- | MagicHash | |
s2q5c47 :: Maybe (Singleton.Singleton Choice.Choice), | |
-- | MonadComprehensions | |
s2q5c48 :: Maybe (Singleton.Singleton Choice.Choice), | |
-- | MonoLocalBinds | |
s2q5c49 :: Maybe (Singleton.Singleton Choice.Choice), | |
-- | MultiParamTypeClasses | |
s2q5c50 :: Maybe (Singleton.Singleton Choice.Choice), | |
-- | MultiWayIf | |
s2q5c51 :: Maybe (Singleton.Singleton Choice.Choice), | |
-- | NamedFieldPuns | |
s2q5c52 :: Maybe (Singleton.Singleton Choice.Choice), | |
-- | NamedWildCards | |
s2q5c53 :: Maybe (Singleton.Singleton Choice.Choice), | |
-- | NegativeLiterals | |
s2q5c54 :: Maybe (Singleton.Singleton Choice.Choice), | |
-- | NoEmptyDataDecls | |
s2q5c55 :: Maybe (Singleton.Singleton Choice.Choice), | |
-- | NoFieldSelectors | |
s2q5c56 :: Maybe (Singleton.Singleton Choice.Choice), | |
-- | NoImplicitPrelude | |
s2q5c57 :: Maybe (Singleton.Singleton Choice.Choice), | |
-- | NoMonadFailDesugaring | |
s2q5c58 :: Maybe (Singleton.Singleton Choice.Choice), | |
-- | NoMonomorphismRestriction | |
s2q5c59 :: Maybe (Singleton.Singleton Choice.Choice), | |
-- | NoPatternGuards | |
s2q5c60 :: Maybe (Singleton.Singleton Choice.Choice), | |
-- | NoStarIsType | |
s2q5c61 :: Maybe (Singleton.Singleton Choice.Choice), | |
-- | NoTraditionalRecordSyntax | |
s2q5c62 :: Maybe (Singleton.Singleton Choice.Choice), | |
-- | NPlusKPatterns | |
s2q5c63 :: Maybe (Singleton.Singleton Choice.Choice), | |
-- | NullaryTypeClasses | |
s2q5c64 :: Maybe (Singleton.Singleton Choice.Choice), | |
-- | NumDecimals | |
s2q5c65 :: Maybe (Singleton.Singleton Choice.Choice), | |
-- | NumericUnderscores | |
s2q5c66 :: Maybe (Singleton.Singleton Choice.Choice), | |
-- | OverlappingInstances | |
s2q5c67 :: Maybe (Singleton.Singleton Choice.Choice), | |
-- | OverloadedLabels | |
s2q5c68 :: Maybe (Singleton.Singleton Choice.Choice), | |
-- | OverloadedLists | |
s2q5c69 :: Maybe (Singleton.Singleton Choice.Choice), | |
-- | OverloadedRecordDot | |
s2q5c70 :: Maybe (Singleton.Singleton Choice.Choice), | |
-- | OverloadedRecordUpdate | |
s2q5c71 :: Maybe (Singleton.Singleton Choice.Choice), | |
-- | OverloadedStrings | |
s2q5c72 :: Maybe (Singleton.Singleton Choice.Choice), | |
-- | PackageImports | |
s2q5c73 :: Maybe (Singleton.Singleton Choice.Choice), | |
-- | ParallelListComp | |
s2q5c74 :: Maybe (Singleton.Singleton Choice.Choice), | |
-- | PartialTypeSignatures | |
s2q5c75 :: Maybe (Singleton.Singleton Choice.Choice), | |
-- | PatternSynonyms | |
s2q5c76 :: Maybe (Singleton.Singleton Choice.Choice), | |
-- | PolyKinds | |
s2q5c77 :: Maybe (Singleton.Singleton Choice.Choice), | |
-- | PostfixOperators | |
s2q5c78 :: Maybe (Singleton.Singleton Choice.Choice), | |
-- | QuantifiedConstraints | |
s2q5c79 :: Maybe (Singleton.Singleton Choice.Choice), | |
-- | QuasiQuotes | |
s2q5c80 :: Maybe (Singleton.Singleton Choice.Choice), | |
-- | Rank2Types | |
s2q5c81 :: Maybe (Singleton.Singleton Choice.Choice), | |
-- | RankNTypes | |
s2q5c82 :: Maybe (Singleton.Singleton Choice.Choice), | |
-- | RebindableSyntax | |
s2q5c83 :: Maybe (Singleton.Singleton Choice.Choice), | |
-- | RecordWildCards | |
s2q5c84 :: Maybe (Singleton.Singleton Choice.Choice), | |
-- | RecursiveDo | |
s2q5c85 :: Maybe (Singleton.Singleton Choice.Choice), | |
-- | RoleAnnotations | |
s2q5c86 :: Maybe (Singleton.Singleton Choice.Choice), | |
-- | ScopedTypeVariables | |
s2q5c87 :: Maybe (Singleton.Singleton Choice.Choice), | |
-- | StandaloneDeriving | |
s2q5c88 :: Maybe (Singleton.Singleton Choice.Choice), | |
-- | StandaloneKindSignatures | |
s2q5c89 :: Maybe (Singleton.Singleton Choice.Choice), | |
-- | StaticPointers | |
s2q5c90 :: Maybe (Singleton.Singleton Choice.Choice), | |
-- | Strict | |
s2q5c91 :: Maybe (Singleton.Singleton Choice.Choice), | |
-- | StrictData | |
s2q5c92 :: Maybe (Singleton.Singleton Choice.Choice), | |
-- | TemplateHaskell | |
s2q5c93 :: Maybe (Singleton.Singleton Choice.Choice), | |
-- | TemplateHaskellQuotes | |
s2q5c94 :: Maybe (Singleton.Singleton Choice.Choice), | |
-- | TransformListComp | |
s2q5c95 :: Maybe (Singleton.Singleton Choice.Choice), | |
-- | Trustworthy | |
s2q5c96 :: Maybe (Singleton.Singleton Choice.Choice), | |
-- | TupleSections | |
s2q5c97 :: Maybe (Singleton.Singleton Choice.Choice), | |
-- | TypeApplications | |
s2q5c98 :: Maybe (Singleton.Singleton Choice.Choice), | |
-- | TypeFamilies | |
s2q5c99 :: Maybe (Singleton.Singleton Choice.Choice), | |
-- | TypeFamilyDependencies | |
s2q5c100 :: Maybe (Singleton.Singleton Choice.Choice), | |
-- | TypeInType | |
s2q5c101 :: Maybe (Singleton.Singleton Choice.Choice), | |
-- | TypeOperators | |
s2q5c102 :: Maybe (Singleton.Singleton Choice.Choice), | |
-- | TypeSynonymInstances | |
s2q5c103 :: Maybe (Singleton.Singleton Choice.Choice), | |
-- | UnboxedSums | |
s2q5c104 :: Maybe (Singleton.Singleton Choice.Choice), | |
-- | UnboxedTuples | |
s2q5c105 :: Maybe (Singleton.Singleton Choice.Choice), | |
-- | UndecidableInstances | |
s2q5c106 :: Maybe (Singleton.Singleton Choice.Choice), | |
-- | UndecidableSuperClasses | |
s2q5c107 :: Maybe (Singleton.Singleton Choice.Choice), | |
-- | UnicodeSyntax | |
s2q5c108 :: Maybe (Singleton.Singleton Choice.Choice), | |
-- | UnliftedDatatypes | |
s2q5c109 :: Maybe (Singleton.Singleton Choice.Choice), | |
-- | UnliftedNewtypes | |
s2q5c110 :: Maybe (Singleton.Singleton Choice.Choice), | |
-- | Unsafe | |
s2q5c111 :: Maybe (Singleton.Singleton Choice.Choice), | |
-- | ViewPatterns | |
s2q5c112 :: Maybe (Singleton.Singleton Choice.Choice), | |
-- | How important do you feel it would be to have a new version of the Haskell language standard? | |
s2q6 :: Maybe (Singleton.Singleton Text.Text), | |
-- | Which build tools do you use for Haskell? | |
s3q0 :: Bag.Bag Text.Text, | |
-- | Which editors do you use for Haskell? | |
s3q1 :: Bag.Bag Text.Text, | |
-- | Which IDEs do you use for Haskell? | |
s3q2 :: Bag.Bag Text.Text, | |
-- | Which version control systems do you use for Haskell? | |
s3q3 :: Bag.Bag Text.Text, | |
-- | Where do you get Haskell packages from? | |
s3q4 :: Bag.Bag Text.Text, | |
-- | Which tools do you use to test Haskell code? | |
s3q5 :: Bag.Bag Text.Text, | |
-- | Which tools do you use to benchmark Haskell code? | |
s3q6 :: Bag.Bag Text.Text, | |
-- | Which tools do you use to deploy Haskell applications? | |
s4q0 :: Bag.Bag Text.Text, | |
-- | Where do you deploy Haskell applications? | |
s4q1 :: Bag.Bag Text.Text, | |
-- | Where do you interact with the Haskell community? | |
s5q0 :: Bag.Bag Text.Text, | |
-- | Which of the following Haskell topics would you like to see more written about? | |
s5q1 :: Bag.Bag Text.Text, | |
-- | I feel welcome in the Haskell community. | |
s6q0 :: Maybe (Singleton.Singleton Text.Text), | |
-- | I am satisfied with Haskell as a language. | |
s6q1 :: Maybe (Singleton.Singleton Text.Text), | |
-- | I am satisfied with Haskell's compilers, such as GHC. | |
s6q2 :: Maybe (Singleton.Singleton Text.Text), | |
-- | I am satisfied with Haskell's build tools, such as Cabal. | |
s6q3 :: Maybe (Singleton.Singleton Text.Text), | |
-- | I am satisfied with Haskell's package repositories, such as Hackage. | |
s6q4 :: Maybe (Singleton.Singleton Text.Text), | |
-- | I can find Haskell libraries for the things that I need. | |
s6q5 :: Maybe (Singleton.Singleton Text.Text), | |
-- | I think Haskell libraries are high quality. | |
s6q6 :: Maybe (Singleton.Singleton Text.Text), | |
-- | I have a good understanding of Haskell best practices. | |
s6q7 :: Maybe (Singleton.Singleton Text.Text), | |
-- | I think Haskell libraries are well documented. | |
s6q8 :: Maybe (Singleton.Singleton Text.Text), | |
-- | I can easily compare competing Haskell libraries to select the best one. | |
s6q9 :: Maybe (Singleton.Singleton Text.Text), | |
-- | I think that Haskell libraries are easy to use. | |
s6q10 :: Maybe (Singleton.Singleton Text.Text), | |
-- | I think that Haskell libraries provide a stable API. | |
s6q11 :: Maybe (Singleton.Singleton Text.Text), | |
-- | I think that Haskell libraries work well together. | |
s6q12 :: Maybe (Singleton.Singleton Text.Text), | |
-- | I think that software written in Haskell is easy to maintain. | |
s6q13 :: Maybe (Singleton.Singleton Text.Text), | |
-- | Once my Haskell program compiles, it generally does what I intended. | |
s6q14 :: Maybe (Singleton.Singleton Text.Text), | |
-- | I think that Haskell libraries perform well. | |
s6q15 :: Maybe (Singleton.Singleton Text.Text), | |
-- | Haskell's performance meets my needs. | |
s6q16 :: Maybe (Singleton.Singleton Text.Text), | |
-- | I can easily reason about the performance of my Haskell code. | |
s6q17 :: Maybe (Singleton.Singleton Text.Text), | |
-- | I would recommend using Haskell to others. | |
s6q18 :: Maybe (Singleton.Singleton Text.Text), | |
-- | I would prefer to use Haskell for my next new project. | |
s6q19 :: Maybe (Singleton.Singleton Text.Text), | |
-- | Haskell is working well for my team. | |
s6q20 :: Maybe (Singleton.Singleton Text.Text), | |
-- | Haskell is critical to my company's success. | |
s6q21 :: Maybe (Singleton.Singleton Text.Text), | |
-- | As a candidate, I can easily find Haskell jobs. | |
s6q22 :: Maybe (Singleton.Singleton Text.Text), | |
-- | As a hiring manager, I can easily find qualified Haskell candidates. | |
s6q23 :: Maybe (Singleton.Singleton Text.Text), | |
-- | Which country do you live in? | |
s7q0 :: Maybe (Singleton.Singleton Text.Text), | |
-- | Do you consider yourself a member of an underrepresented or marginalized group in technology? | |
s7q1 :: Bag.Bag Text.Text, | |
-- | Do you feel your belonging to an underrepresented or marginalized group in technology makes it difficult for you to participate in the Haskell community? | |
s7q2 :: Maybe (Singleton.Singleton Text.Text), | |
-- | Are you a student? | |
s7q3 :: Maybe (Singleton.Singleton Text.Text), | |
-- | What is the highest level of education you have completed? | |
s7q4 :: Maybe (Singleton.Singleton Text.Text), | |
-- | What is your employment status? | |
s7q5 :: Maybe (Singleton.Singleton Text.Text), | |
-- | How large is the company you work for? | |
s7q6 :: Maybe (Singleton.Singleton Text.Text), | |
-- | How many years have you been coding? | |
s7q7 :: Maybe (Singleton.Singleton Text.Text), | |
-- | How many years have you been coding professionally? | |
s7q8 :: Maybe (Singleton.Singleton Text.Text), | |
-- | Do you code as a hobby? | |
s7q9 :: Maybe (Singleton.Singleton Text.Text), | |
-- | Have you contributed to any open source projects? | |
s7q10 :: Maybe (Singleton.Singleton Text.Text), | |
-- | Did you take any previous surveys? | |
s8q0 :: Bag.Bag Text.Text, | |
-- | How did you hear about this survey? | |
s8q1 :: Bag.Bag Text.Text, | |
-- | If you wanted to convince someone to use Haskell, what would you say? | |
s9q0 :: Maybe (Singleton.Singleton Text.Text), | |
-- | If you could change one thing about Haskell, what would it be? | |
s9q1 :: Maybe (Singleton.Singleton Text.Text) | |
} | |
deriving (Eq, Show) | |
instance Aeson.FromJSON Response where | |
parseJSON = Aeson.withObject "Response" $ \object -> do | |
startedAt <- required object "started-at" | |
finishedAt <- required object "finished-at" | |
s0q0 <- | |
Choice.Choice | |
. not | |
. Text.all Char.isSpace | |
. maybe Text.empty Singleton.unwrap | |
<$> optional object "section-0-question-0" | |
s0q1 <- optional object "section-0-question-1" | |
s0q2 <- optional object "section-0-question-2" | |
s0q3 <- withDefault Bag.empty $ optional object "section-0-question-3" | |
s0q4 <- optional object "section-0-question-4" | |
s0q5 <- optional object "section-0-question-5" | |
s0q6 <- optional object "section-0-question-6" | |
s0q7 <- withDefault Bag.empty $ optional object "section-0-question-7" | |
s0q8 <- optional object "section-0-question-8" | |
s0q9 <- withDefault Bag.empty $ optional object "section-0-question-9" | |
s0q10 <- withDefault Bag.empty $ optional object "section-0-question-10" | |
s0q11 <- withDefault Bag.empty $ optional object "section-0-question-11" | |
s0q12 <- withDefault Bag.empty $ optional object "section-0-question-12" | |
s1q0 <- optional object "section-1-question-0" | |
s1q1 <- optional object "section-1-question-1" | |
s1q2 <- withDefault Bag.empty $ optional object "section-1-question-2" | |
s1q3 <- withDefault Bag.empty $ optional object "section-1-question-3" | |
s2q0 <- withDefault Bag.empty $ optional object "section-2-question-0" | |
s2q1 <- withDefault Bag.empty $ optional object "section-2-question-1" | |
s2q2 <- optional object "section-2-question-2" | |
s2q3 <- withDefault Bag.empty $ optional object "section-2-question-3" | |
s2q4 <- withDefault Bag.empty $ optional object "section-2-question-4" | |
s2q5c0 <- optional object "section-2-question-5-choice-0" | |
s2q5c1 <- optional object "section-2-question-5-choice-1" | |
s2q5c2 <- optional object "section-2-question-5-choice-2" | |
s2q5c3 <- optional object "section-2-question-5-choice-3" | |
s2q5c4 <- optional object "section-2-question-5-choice-4" | |
s2q5c5 <- optional object "section-2-question-5-choice-5" | |
s2q5c6 <- optional object "section-2-question-5-choice-6" | |
s2q5c7 <- optional object "section-2-question-5-choice-7" | |
s2q5c8 <- optional object "section-2-question-5-choice-8" | |
s2q5c9 <- optional object "section-2-question-5-choice-9" | |
s2q5c10 <- optional object "section-2-question-5-choice-10" | |
s2q5c11 <- optional object "section-2-question-5-choice-11" | |
s2q5c12 <- optional object "section-2-question-5-choice-12" | |
s2q5c13 <- optional object "section-2-question-5-choice-13" | |
s2q5c14 <- optional object "section-2-question-5-choice-14" | |
s2q5c15 <- optional object "section-2-question-5-choice-15" | |
s2q5c16 <- optional object "section-2-question-5-choice-16" | |
s2q5c17 <- optional object "section-2-question-5-choice-17" | |
s2q5c18 <- optional object "section-2-question-5-choice-18" | |
s2q5c19 <- optional object "section-2-question-5-choice-19" | |
s2q5c20 <- optional object "section-2-question-5-choice-20" | |
s2q5c21 <- optional object "section-2-question-5-choice-21" | |
s2q5c22 <- optional object "section-2-question-5-choice-22" | |
s2q5c23 <- optional object "section-2-question-5-choice-23" | |
s2q5c24 <- optional object "section-2-question-5-choice-24" | |
s2q5c25 <- optional object "section-2-question-5-choice-25" | |
s2q5c26 <- optional object "section-2-question-5-choice-26" | |
s2q5c27 <- optional object "section-2-question-5-choice-27" | |
s2q5c28 <- optional object "section-2-question-5-choice-28" | |
s2q5c29 <- optional object "section-2-question-5-choice-29" | |
s2q5c30 <- optional object "section-2-question-5-choice-30" | |
s2q5c31 <- optional object "section-2-question-5-choice-31" | |
s2q5c32 <- optional object "section-2-question-5-choice-32" | |
s2q5c33 <- optional object "section-2-question-5-choice-33" | |
s2q5c34 <- optional object "section-2-question-5-choice-34" | |
s2q5c35 <- optional object "section-2-question-5-choice-35" | |
s2q5c36 <- optional object "section-2-question-5-choice-36" | |
s2q5c37 <- optional object "section-2-question-5-choice-37" | |
s2q5c38 <- optional object "section-2-question-5-choice-38" | |
s2q5c39 <- optional object "section-2-question-5-choice-39" | |
s2q5c40 <- optional object "section-2-question-5-choice-40" | |
s2q5c41 <- optional object "section-2-question-5-choice-41" | |
s2q5c42 <- optional object "section-2-question-5-choice-42" | |
s2q5c43 <- optional object "section-2-question-5-choice-43" | |
s2q5c44 <- optional object "section-2-question-5-choice-44" | |
s2q5c45 <- optional object "section-2-question-5-choice-45" | |
s2q5c46 <- optional object "section-2-question-5-choice-46" | |
s2q5c47 <- optional object "section-2-question-5-choice-47" | |
s2q5c48 <- optional object "section-2-question-5-choice-48" | |
s2q5c49 <- optional object "section-2-question-5-choice-49" | |
s2q5c50 <- optional object "section-2-question-5-choice-50" | |
s2q5c51 <- optional object "section-2-question-5-choice-51" | |
s2q5c52 <- optional object "section-2-question-5-choice-52" | |
s2q5c53 <- optional object "section-2-question-5-choice-53" | |
s2q5c54 <- optional object "section-2-question-5-choice-54" | |
s2q5c55 <- optional object "section-2-question-5-choice-55" | |
s2q5c56 <- optional object "section-2-question-5-choice-56" | |
s2q5c57 <- optional object "section-2-question-5-choice-57" | |
s2q5c58 <- optional object "section-2-question-5-choice-58" | |
s2q5c59 <- optional object "section-2-question-5-choice-59" | |
s2q5c60 <- optional object "section-2-question-5-choice-60" | |
s2q5c61 <- optional object "section-2-question-5-choice-61" | |
s2q5c62 <- optional object "section-2-question-5-choice-62" | |
s2q5c63 <- optional object "section-2-question-5-choice-63" | |
s2q5c64 <- optional object "section-2-question-5-choice-64" | |
s2q5c65 <- optional object "section-2-question-5-choice-65" | |
s2q5c66 <- optional object "section-2-question-5-choice-66" | |
s2q5c67 <- optional object "section-2-question-5-choice-67" | |
s2q5c68 <- optional object "section-2-question-5-choice-68" | |
s2q5c69 <- optional object "section-2-question-5-choice-69" | |
s2q5c70 <- optional object "section-2-question-5-choice-70" | |
s2q5c71 <- optional object "section-2-question-5-choice-71" | |
s2q5c72 <- optional object "section-2-question-5-choice-72" | |
s2q5c73 <- optional object "section-2-question-5-choice-73" | |
s2q5c74 <- optional object "section-2-question-5-choice-74" | |
s2q5c75 <- optional object "section-2-question-5-choice-75" | |
s2q5c76 <- optional object "section-2-question-5-choice-76" | |
s2q5c77 <- optional object "section-2-question-5-choice-77" | |
s2q5c78 <- optional object "section-2-question-5-choice-78" | |
s2q5c79 <- optional object "section-2-question-5-choice-79" | |
s2q5c80 <- optional object "section-2-question-5-choice-80" | |
s2q5c81 <- optional object "section-2-question-5-choice-81" | |
s2q5c82 <- optional object "section-2-question-5-choice-82" | |
s2q5c83 <- optional object "section-2-question-5-choice-83" | |
s2q5c84 <- optional object "section-2-question-5-choice-84" | |
s2q5c85 <- optional object "section-2-question-5-choice-85" | |
s2q5c86 <- optional object "section-2-question-5-choice-86" | |
s2q5c87 <- optional object "section-2-question-5-choice-87" | |
s2q5c88 <- optional object "section-2-question-5-choice-88" | |
s2q5c89 <- optional object "section-2-question-5-choice-89" | |
s2q5c90 <- optional object "section-2-question-5-choice-90" | |
s2q5c91 <- optional object "section-2-question-5-choice-91" | |
s2q5c92 <- optional object "section-2-question-5-choice-92" | |
s2q5c93 <- optional object "section-2-question-5-choice-93" | |
s2q5c94 <- optional object "section-2-question-5-choice-94" | |
s2q5c95 <- optional object "section-2-question-5-choice-95" | |
s2q5c96 <- optional object "section-2-question-5-choice-96" | |
s2q5c97 <- optional object "section-2-question-5-choice-97" | |
s2q5c98 <- optional object "section-2-question-5-choice-98" | |
s2q5c99 <- optional object "section-2-question-5-choice-99" | |
s2q5c100 <- optional object "section-2-question-5-choice-100" | |
s2q5c101 <- optional object "section-2-question-5-choice-101" | |
s2q5c102 <- optional object "section-2-question-5-choice-102" | |
s2q5c103 <- optional object "section-2-question-5-choice-103" | |
s2q5c104 <- optional object "section-2-question-5-choice-104" | |
s2q5c105 <- optional object "section-2-question-5-choice-105" | |
s2q5c106 <- optional object "section-2-question-5-choice-106" | |
s2q5c107 <- optional object "section-2-question-5-choice-107" | |
s2q5c108 <- optional object "section-2-question-5-choice-108" | |
s2q5c109 <- optional object "section-2-question-5-choice-109" | |
s2q5c110 <- optional object "section-2-question-5-choice-110" | |
s2q5c111 <- optional object "section-2-question-5-choice-111" | |
s2q5c112 <- optional object "section-2-question-5-choice-112" | |
s2q6 <- optional object "section-2-question-6" | |
s3q0 <- withDefault Bag.empty $ optional object "section-3-question-0" | |
s3q1 <- withDefault Bag.empty $ optional object "section-3-question-1" | |
s3q2 <- withDefault Bag.empty $ optional object "section-3-question-2" | |
s3q3 <- withDefault Bag.empty $ optional object "section-3-question-3" | |
s3q4 <- withDefault Bag.empty $ optional object "section-3-question-4" | |
s3q5 <- withDefault Bag.empty $ optional object "section-3-question-5" | |
s3q6 <- withDefault Bag.empty $ optional object "section-3-question-6" | |
s4q0 <- withDefault Bag.empty $ optional object "section-4-question-0" | |
s4q1 <- withDefault Bag.empty $ optional object "section-4-question-1" | |
s5q0 <- withDefault Bag.empty $ optional object "section-5-question-0" | |
s5q1 <- withDefault Bag.empty $ optional object "section-5-question-1" | |
s6q0 <- optional object "section-6-question-0" | |
s6q1 <- optional object "section-6-question-1" | |
s6q2 <- optional object "section-6-question-2" | |
s6q3 <- optional object "section-6-question-3" | |
s6q4 <- optional object "section-6-question-4" | |
s6q5 <- optional object "section-6-question-5" | |
s6q6 <- optional object "section-6-question-6" | |
s6q7 <- optional object "section-6-question-7" | |
s6q8 <- optional object "section-6-question-8" | |
s6q9 <- optional object "section-6-question-9" | |
s6q10 <- optional object "section-6-question-10" | |
s6q11 <- optional object "section-6-question-11" | |
s6q12 <- optional object "section-6-question-12" | |
s6q13 <- optional object "section-6-question-13" | |
s6q14 <- optional object "section-6-question-14" | |
s6q15 <- optional object "section-6-question-15" | |
s6q16 <- optional object "section-6-question-16" | |
s6q17 <- optional object "section-6-question-17" | |
s6q18 <- optional object "section-6-question-18" | |
s6q19 <- optional object "section-6-question-19" | |
s6q20 <- optional object "section-6-question-20" | |
s6q21 <- optional object "section-6-question-21" | |
s6q22 <- optional object "section-6-question-22" | |
s6q23 <- optional object "section-6-question-23" | |
s7q0 <- optional object "section-7-question-0" | |
s7q1 <- withDefault Bag.empty $ optional object "section-7-question-1" | |
s7q2 <- optional object "section-7-question-2" | |
s7q3 <- optional object "section-7-question-3" | |
s7q4 <- optional object "section-7-question-4" | |
s7q5 <- optional object "section-7-question-5" | |
s7q6 <- optional object "section-7-question-6" | |
s7q7 <- optional object "section-7-question-7" | |
s7q8 <- optional object "section-7-question-8" | |
s7q9 <- optional object "section-7-question-9" | |
s7q10 <- optional object "section-7-question-10" | |
s8q0 <- withDefault Bag.empty $ optional object "section-8-question-0" | |
s8q1 <- withDefault Bag.empty $ optional object "section-8-question-1" | |
s9q0 <- optional object "section-9-question-0" | |
s9q1 <- optional object "section-9-question-1" | |
pure | |
Response | |
{ startedAt, | |
finishedAt, | |
s0q0, | |
s0q1, | |
s0q2, | |
s0q3, | |
s0q4, | |
s0q5, | |
s0q6, | |
s0q7, | |
s0q8, | |
s0q9, | |
s0q10, | |
s0q11, | |
s0q12, | |
s1q0, | |
s1q1, | |
s1q2, | |
s1q3, | |
s2q0, | |
s2q1, | |
s2q2, | |
s2q3, | |
s2q4, | |
s2q5c0, | |
s2q5c1, | |
s2q5c2, | |
s2q5c3, | |
s2q5c4, | |
s2q5c5, | |
s2q5c6, | |
s2q5c7, | |
s2q5c8, | |
s2q5c9, | |
s2q5c10, | |
s2q5c11, | |
s2q5c12, | |
s2q5c13, | |
s2q5c14, | |
s2q5c15, | |
s2q5c16, | |
s2q5c17, | |
s2q5c18, | |
s2q5c19, | |
s2q5c20, | |
s2q5c21, | |
s2q5c22, | |
s2q5c23, | |
s2q5c24, | |
s2q5c25, | |
s2q5c26, | |
s2q5c27, | |
s2q5c28, | |
s2q5c29, | |
s2q5c30, | |
s2q5c31, | |
s2q5c32, | |
s2q5c33, | |
s2q5c34, | |
s2q5c35, | |
s2q5c36, | |
s2q5c37, | |
s2q5c38, | |
s2q5c39, | |
s2q5c40, | |
s2q5c41, | |
s2q5c42, | |
s2q5c43, | |
s2q5c44, | |
s2q5c45, | |
s2q5c46, | |
s2q5c47, | |
s2q5c48, | |
s2q5c49, | |
s2q5c50, | |
s2q5c51, | |
s2q5c52, | |
s2q5c53, | |
s2q5c54, | |
s2q5c55, | |
s2q5c56, | |
s2q5c57, | |
s2q5c58, | |
s2q5c59, | |
s2q5c60, | |
s2q5c61, | |
s2q5c62, | |
s2q5c63, | |
s2q5c64, | |
s2q5c65, | |
s2q5c66, | |
s2q5c67, | |
s2q5c68, | |
s2q5c69, | |
s2q5c70, | |
s2q5c71, | |
s2q5c72, | |
s2q5c73, | |
s2q5c74, | |
s2q5c75, | |
s2q5c76, | |
s2q5c77, | |
s2q5c78, | |
s2q5c79, | |
s2q5c80, | |
s2q5c81, | |
s2q5c82, | |
s2q5c83, | |
s2q5c84, | |
s2q5c85, | |
s2q5c86, | |
s2q5c87, | |
s2q5c88, | |
s2q5c89, | |
s2q5c90, | |
s2q5c91, | |
s2q5c92, | |
s2q5c93, | |
s2q5c94, | |
s2q5c95, | |
s2q5c96, | |
s2q5c97, | |
s2q5c98, | |
s2q5c99, | |
s2q5c100, | |
s2q5c101, | |
s2q5c102, | |
s2q5c103, | |
s2q5c104, | |
s2q5c105, | |
s2q5c106, | |
s2q5c107, | |
s2q5c108, | |
s2q5c109, | |
s2q5c110, | |
s2q5c111, | |
s2q5c112, | |
s2q6, | |
s3q0, | |
s3q1, | |
s3q2, | |
s3q3, | |
s3q4, | |
s3q5, | |
s3q6, | |
s4q0, | |
s4q1, | |
s5q0, | |
s5q1, | |
s6q0, | |
s6q1, | |
s6q2, | |
s6q3, | |
s6q4, | |
s6q5, | |
s6q6, | |
s6q7, | |
s6q8, | |
s6q9, | |
s6q10, | |
s6q11, | |
s6q12, | |
s6q13, | |
s6q14, | |
s6q15, | |
s6q16, | |
s6q17, | |
s6q18, | |
s6q19, | |
s6q20, | |
s6q21, | |
s6q22, | |
s6q23, | |
s7q0, | |
s7q1, | |
s7q2, | |
s7q3, | |
s7q4, | |
s7q5, | |
s7q6, | |
s7q7, | |
s7q8, | |
s7q9, | |
s7q10, | |
s8q0, | |
s8q1, | |
s9q0, | |
s9q1 | |
} | |
instance Aeson.ToJSON Response where | |
toJSON x = | |
Aeson.object | |
[ pair "startedAt" $ startedAt x, | |
pair "finishedAt" $ finishedAt x, | |
pair "s0q0" $ s0q0 x, | |
pair "s0q1" $ s0q1 x, | |
pair "s0q2" $ s0q2 x, | |
pair "s0q3" $ s0q3 x, | |
pair "s0q4" $ s0q4 x, | |
pair "s0q5" $ s0q5 x, | |
pair "s0q6" $ s0q6 x, | |
pair "s0q7" $ s0q7 x, | |
pair "s0q8" $ s0q8 x, | |
pair "s0q9" $ s0q9 x, | |
pair "s0q10" $ s0q10 x, | |
pair "s0q11" $ s0q11 x, | |
pair "s0q12" $ s0q12 x, | |
pair "s1q0" $ s1q0 x, | |
pair "s1q1" $ s1q1 x, | |
pair "s1q2" $ s1q2 x, | |
pair "s1q3" $ s1q3 x, | |
pair "s2q0" $ s2q0 x, | |
pair "s2q1" $ s2q1 x, | |
pair "s2q2" $ s2q2 x, | |
pair "s2q3" $ s2q3 x, | |
pair "s2q4" $ s2q4 x, | |
pair "s2q5c0" $ s2q5c0 x, | |
pair "s2q5c1" $ s2q5c1 x, | |
pair "s2q5c2" $ s2q5c2 x, | |
pair "s2q5c3" $ s2q5c3 x, | |
pair "s2q5c4" $ s2q5c4 x, | |
pair "s2q5c5" $ s2q5c5 x, | |
pair "s2q5c6" $ s2q5c6 x, | |
pair "s2q5c7" $ s2q5c7 x, | |
pair "s2q5c8" $ s2q5c8 x, | |
pair "s2q5c9" $ s2q5c9 x, | |
pair "s2q5c10" $ s2q5c10 x, | |
pair "s2q5c11" $ s2q5c11 x, | |
pair "s2q5c12" $ s2q5c12 x, | |
pair "s2q5c13" $ s2q5c13 x, | |
pair "s2q5c14" $ s2q5c14 x, | |
pair "s2q5c15" $ s2q5c15 x, | |
pair "s2q5c16" $ s2q5c16 x, | |
pair "s2q5c17" $ s2q5c17 x, | |
pair "s2q5c18" $ s2q5c18 x, | |
pair "s2q5c19" $ s2q5c19 x, | |
pair "s2q5c20" $ s2q5c20 x, | |
pair "s2q5c21" $ s2q5c21 x, | |
pair "s2q5c22" $ s2q5c22 x, | |
pair "s2q5c23" $ s2q5c23 x, | |
pair "s2q5c24" $ s2q5c24 x, | |
pair "s2q5c25" $ s2q5c25 x, | |
pair "s2q5c26" $ s2q5c26 x, | |
pair "s2q5c27" $ s2q5c27 x, | |
pair "s2q5c28" $ s2q5c28 x, | |
pair "s2q5c29" $ s2q5c29 x, | |
pair "s2q5c30" $ s2q5c30 x, | |
pair "s2q5c31" $ s2q5c31 x, | |
pair "s2q5c32" $ s2q5c32 x, | |
pair "s2q5c33" $ s2q5c33 x, | |
pair "s2q5c34" $ s2q5c34 x, | |
pair "s2q5c35" $ s2q5c35 x, | |
pair "s2q5c36" $ s2q5c36 x, | |
pair "s2q5c37" $ s2q5c37 x, | |
pair "s2q5c38" $ s2q5c38 x, | |
pair "s2q5c39" $ s2q5c39 x, | |
pair "s2q5c40" $ s2q5c40 x, | |
pair "s2q5c41" $ s2q5c41 x, | |
pair "s2q5c42" $ s2q5c42 x, | |
pair "s2q5c43" $ s2q5c43 x, | |
pair "s2q5c44" $ s2q5c44 x, | |
pair "s2q5c45" $ s2q5c45 x, | |
pair "s2q5c46" $ s2q5c46 x, | |
pair "s2q5c47" $ s2q5c47 x, | |
pair "s2q5c48" $ s2q5c48 x, | |
pair "s2q5c49" $ s2q5c49 x, | |
pair "s2q5c50" $ s2q5c50 x, | |
pair "s2q5c51" $ s2q5c51 x, | |
pair "s2q5c52" $ s2q5c52 x, | |
pair "s2q5c53" $ s2q5c53 x, | |
pair "s2q5c54" $ s2q5c54 x, | |
pair "s2q5c55" $ s2q5c55 x, | |
pair "s2q5c56" $ s2q5c56 x, | |
pair "s2q5c57" $ s2q5c57 x, | |
pair "s2q5c58" $ s2q5c58 x, | |
pair "s2q5c59" $ s2q5c59 x, | |
pair "s2q5c60" $ s2q5c60 x, | |
pair "s2q5c61" $ s2q5c61 x, | |
pair "s2q5c62" $ s2q5c62 x, | |
pair "s2q5c63" $ s2q5c63 x, | |
pair "s2q5c64" $ s2q5c64 x, | |
pair "s2q5c65" $ s2q5c65 x, | |
pair "s2q5c66" $ s2q5c66 x, | |
pair "s2q5c67" $ s2q5c67 x, | |
pair "s2q5c68" $ s2q5c68 x, | |
pair "s2q5c69" $ s2q5c69 x, | |
pair "s2q5c70" $ s2q5c70 x, | |
pair "s2q5c71" $ s2q5c71 x, | |
pair "s2q5c72" $ s2q5c72 x, | |
pair "s2q5c73" $ s2q5c73 x, | |
pair "s2q5c74" $ s2q5c74 x, | |
pair "s2q5c75" $ s2q5c75 x, | |
pair "s2q5c76" $ s2q5c76 x, | |
pair "s2q5c77" $ s2q5c77 x, | |
pair "s2q5c78" $ s2q5c78 x, | |
pair "s2q5c79" $ s2q5c79 x, | |
pair "s2q5c80" $ s2q5c80 x, | |
pair "s2q5c81" $ s2q5c81 x, | |
pair "s2q5c82" $ s2q5c82 x, | |
pair "s2q5c83" $ s2q5c83 x, | |
pair "s2q5c84" $ s2q5c84 x, | |
pair "s2q5c85" $ s2q5c85 x, | |
pair "s2q5c86" $ s2q5c86 x, | |
pair "s2q5c87" $ s2q5c87 x, | |
pair "s2q5c88" $ s2q5c88 x, | |
pair "s2q5c89" $ s2q5c89 x, | |
pair "s2q5c90" $ s2q5c90 x, | |
pair "s2q5c91" $ s2q5c91 x, | |
pair "s2q5c92" $ s2q5c92 x, | |
pair "s2q5c93" $ s2q5c93 x, | |
pair "s2q5c94" $ s2q5c94 x, | |
pair "s2q5c95" $ s2q5c95 x, | |
pair "s2q5c96" $ s2q5c96 x, | |
pair "s2q5c97" $ s2q5c97 x, | |
pair "s2q5c98" $ s2q5c98 x, | |
pair "s2q5c99" $ s2q5c99 x, | |
pair "s2q5c100" $ s2q5c100 x, | |
pair "s2q5c101" $ s2q5c101 x, | |
pair "s2q5c102" $ s2q5c102 x, | |
pair "s2q5c103" $ s2q5c103 x, | |
pair "s2q5c104" $ s2q5c104 x, | |
pair "s2q5c105" $ s2q5c105 x, | |
pair "s2q5c106" $ s2q5c106 x, | |
pair "s2q5c107" $ s2q5c107 x, | |
pair "s2q5c108" $ s2q5c108 x, | |
pair "s2q5c109" $ s2q5c109 x, | |
pair "s2q5c110" $ s2q5c110 x, | |
pair "s2q5c111" $ s2q5c111 x, | |
pair "s2q5c112" $ s2q5c112 x, | |
pair "s2q6" $ s2q6 x, | |
pair "s3q0" $ s3q0 x, | |
pair "s3q1" $ s3q1 x, | |
pair "s3q2" $ s3q2 x, | |
pair "s3q3" $ s3q3 x, | |
pair "s3q4" $ s3q4 x, | |
pair "s3q5" $ s3q5 x, | |
pair "s3q6" $ s3q6 x, | |
pair "s4q0" $ s4q0 x, | |
pair "s4q1" $ s4q1 x, | |
pair "s5q0" $ s5q0 x, | |
pair "s5q1" $ s5q1 x, | |
pair "s6q0" $ s6q0 x, | |
pair "s6q1" $ s6q1 x, | |
pair "s6q2" $ s6q2 x, | |
pair "s6q3" $ s6q3 x, | |
pair "s6q4" $ s6q4 x, | |
pair "s6q5" $ s6q5 x, | |
pair "s6q6" $ s6q6 x, | |
pair "s6q7" $ s6q7 x, | |
pair "s6q8" $ s6q8 x, | |
pair "s6q9" $ s6q9 x, | |
pair "s6q10" $ s6q10 x, | |
pair "s6q11" $ s6q11 x, | |
pair "s6q12" $ s6q12 x, | |
pair "s6q13" $ s6q13 x, | |
pair "s6q14" $ s6q14 x, | |
pair "s6q15" $ s6q15 x, | |
pair "s6q16" $ s6q16 x, | |
pair "s6q17" $ s6q17 x, | |
pair "s6q18" $ s6q18 x, | |
pair "s6q19" $ s6q19 x, | |
pair "s6q20" $ s6q20 x, | |
pair "s6q21" $ s6q21 x, | |
pair "s6q22" $ s6q22 x, | |
pair "s6q23" $ s6q23 x, | |
pair "s7q0" $ s7q0 x, | |
pair "s7q1" $ s7q1 x, | |
pair "s7q2" $ s7q2 x, | |
pair "s7q3" $ s7q3 x, | |
pair "s7q4" $ s7q4 x, | |
pair "s7q5" $ s7q5 x, | |
pair "s7q6" $ s7q6 x, | |
pair "s7q7" $ s7q7 x, | |
pair "s7q8" $ s7q8 x, | |
pair "s7q9" $ s7q9 x, | |
pair "s7q10" $ s7q10 x, | |
pair "s8q0" $ s8q0 x, | |
pair "s8q1" $ s8q1 x, | |
pair "s9q0" $ s9q0 x, | |
pair "s9q1" $ s9q1 x | |
] | |
instance Csv.DefaultOrdered Response where | |
headerOrder = const . Vector.fromList $ fmap fst fields | |
instance Csv.ToNamedRecord Response where | |
toNamedRecord x = Csv.namedRecord $ fmap (\(n, f) -> Csv.namedField n $ f x) fields | |
fields :: [(Csv.Name, Response -> Csv.Field)] | |
fields = | |
[ field "startedAt" startedAt, | |
field "finishedAt" finishedAt, | |
field "s0q0" s0q0, | |
field "s0q1" s0q1, | |
field "s0q2" s0q2, | |
field "s0q3" s0q3, | |
field "s0q4" s0q4, | |
field "s0q5" s0q5, | |
field "s0q6" s0q6, | |
field "s0q7" s0q7, | |
field "s0q8" s0q8, | |
field "s0q9" s0q9, | |
field "s0q10" s0q10, | |
field "s0q11" s0q11, | |
field "s0q12" s0q12, | |
field "s1q0" s1q0, | |
field "s1q1" s1q1, | |
field "s1q2" s1q2, | |
field "s1q3" s1q3, | |
field "s2q0" s2q0, | |
field "s2q1" s2q1, | |
field "s2q2" s2q2, | |
field "s2q3" s2q3, | |
field "s2q4" s2q4, | |
field "s2q5c0" s2q5c0, | |
field "s2q5c1" s2q5c1, | |
field "s2q5c2" s2q5c2, | |
field "s2q5c3" s2q5c3, | |
field "s2q5c4" s2q5c4, | |
field "s2q5c5" s2q5c5, | |
field "s2q5c6" s2q5c6, | |
field "s2q5c7" s2q5c7, | |
field "s2q5c8" s2q5c8, | |
field "s2q5c9" s2q5c9, | |
field "s2q5c10" s2q5c10, | |
field "s2q5c11" s2q5c11, | |
field "s2q5c12" s2q5c12, | |
field "s2q5c13" s2q5c13, | |
field "s2q5c14" s2q5c14, | |
field "s2q5c15" s2q5c15, | |
field "s2q5c16" s2q5c16, | |
field "s2q5c17" s2q5c17, | |
field "s2q5c18" s2q5c18, | |
field "s2q5c19" s2q5c19, | |
field "s2q5c20" s2q5c20, | |
field "s2q5c21" s2q5c21, | |
field "s2q5c22" s2q5c22, | |
field "s2q5c23" s2q5c23, | |
field "s2q5c24" s2q5c24, | |
field "s2q5c25" s2q5c25, | |
field "s2q5c26" s2q5c26, | |
field "s2q5c27" s2q5c27, | |
field "s2q5c28" s2q5c28, | |
field "s2q5c29" s2q5c29, | |
field "s2q5c30" s2q5c30, | |
field "s2q5c31" s2q5c31, | |
field "s2q5c32" s2q5c32, | |
field "s2q5c33" s2q5c33, | |
field "s2q5c34" s2q5c34, | |
field "s2q5c35" s2q5c35, | |
field "s2q5c36" s2q5c36, | |
field "s2q5c37" s2q5c37, | |
field "s2q5c38" s2q5c38, | |
field "s2q5c39" s2q5c39, | |
field "s2q5c40" s2q5c40, | |
field "s2q5c41" s2q5c41, | |
field "s2q5c42" s2q5c42, | |
field "s2q5c43" s2q5c43, | |
field "s2q5c44" s2q5c44, | |
field "s2q5c45" s2q5c45, | |
field "s2q5c46" s2q5c46, | |
field "s2q5c47" s2q5c47, | |
field "s2q5c48" s2q5c48, | |
field "s2q5c49" s2q5c49, | |
field "s2q5c50" s2q5c50, | |
field "s2q5c51" s2q5c51, | |
field "s2q5c52" s2q5c52, | |
field "s2q5c53" s2q5c53, | |
field "s2q5c54" s2q5c54, | |
field "s2q5c55" s2q5c55, | |
field "s2q5c56" s2q5c56, | |
field "s2q5c57" s2q5c57, | |
field "s2q5c58" s2q5c58, | |
field "s2q5c59" s2q5c59, | |
field "s2q5c60" s2q5c60, | |
field "s2q5c61" s2q5c61, | |
field "s2q5c62" s2q5c62, | |
field "s2q5c63" s2q5c63, | |
field "s2q5c64" s2q5c64, | |
field "s2q5c65" s2q5c65, | |
field "s2q5c66" s2q5c66, | |
field "s2q5c67" s2q5c67, | |
field "s2q5c68" s2q5c68, | |
field "s2q5c69" s2q5c69, | |
field "s2q5c70" s2q5c70, | |
field "s2q5c71" s2q5c71, | |
field "s2q5c72" s2q5c72, | |
field "s2q5c73" s2q5c73, | |
field "s2q5c74" s2q5c74, | |
field "s2q5c75" s2q5c75, | |
field "s2q5c76" s2q5c76, | |
field "s2q5c77" s2q5c77, | |
field "s2q5c78" s2q5c78, | |
field "s2q5c79" s2q5c79, | |
field "s2q5c80" s2q5c80, | |
field "s2q5c81" s2q5c81, | |
field "s2q5c82" s2q5c82, | |
field "s2q5c83" s2q5c83, | |
field "s2q5c84" s2q5c84, | |
field "s2q5c85" s2q5c85, | |
field "s2q5c86" s2q5c86, | |
field "s2q5c87" s2q5c87, | |
field "s2q5c88" s2q5c88, | |
field "s2q5c89" s2q5c89, | |
field "s2q5c90" s2q5c90, | |
field "s2q5c91" s2q5c91, | |
field "s2q5c92" s2q5c92, | |
field "s2q5c93" s2q5c93, | |
field "s2q5c94" s2q5c94, | |
field "s2q5c95" s2q5c95, | |
field "s2q5c96" s2q5c96, | |
field "s2q5c97" s2q5c97, | |
field "s2q5c98" s2q5c98, | |
field "s2q5c99" s2q5c99, | |
field "s2q5c100" s2q5c100, | |
field "s2q5c101" s2q5c101, | |
field "s2q5c102" s2q5c102, | |
field "s2q5c103" s2q5c103, | |
field "s2q5c104" s2q5c104, | |
field "s2q5c105" s2q5c105, | |
field "s2q5c106" s2q5c106, | |
field "s2q5c107" s2q5c107, | |
field "s2q5c108" s2q5c108, | |
field "s2q5c109" s2q5c109, | |
field "s2q5c110" s2q5c110, | |
field "s2q5c111" s2q5c111, | |
field "s2q5c112" s2q5c112, | |
field "s2q6" s2q6, | |
field "s3q0" s3q0, | |
field "s3q1" s3q1, | |
field "s3q2" s3q2, | |
field "s3q3" s3q3, | |
field "s3q4" s3q4, | |
field "s3q5" s3q5, | |
field "s3q6" s3q6, | |
field "s4q0" s4q0, | |
field "s4q1" s4q1, | |
field "s5q0" s5q0, | |
field "s5q1" s5q1, | |
field "s6q0" s6q0, | |
field "s6q1" s6q1, | |
field "s6q2" s6q2, | |
field "s6q3" s6q3, | |
field "s6q4" s6q4, | |
field "s6q5" s6q5, | |
field "s6q6" s6q6, | |
field "s6q7" s6q7, | |
field "s6q8" s6q8, | |
field "s6q9" s6q9, | |
field "s6q10" s6q10, | |
field "s6q11" s6q11, | |
field "s6q12" s6q12, | |
field "s6q13" s6q13, | |
field "s6q14" s6q14, | |
field "s6q15" s6q15, | |
field "s6q16" s6q16, | |
field "s6q17" s6q17, | |
field "s6q18" s6q18, | |
field "s6q19" s6q19, | |
field "s6q20" s6q20, | |
field "s6q21" s6q21, | |
field "s6q22" s6q22, | |
field "s6q23" s6q23, | |
field "s7q0" s7q0, | |
field "s7q1" s7q1, | |
field "s7q2" s7q2, | |
field "s7q3" s7q3, | |
field "s7q4" s7q4, | |
field "s7q5" s7q5, | |
field "s7q6" s7q6, | |
field "s7q7" s7q7, | |
field "s7q8" s7q8, | |
field "s7q9" s7q9, | |
field "s7q10" s7q10, | |
field "s8q0" s8q0, | |
field "s8q1" s8q1, | |
field "s9q0" s9q0, | |
field "s9q1" s9q1 | |
] | |
required :: Aeson.FromJSON a => Aeson.Object -> String -> Aeson.Parser a | |
required object key = object Aeson..: Key.fromString key | |
optional :: Aeson.FromJSON a => Aeson.Object -> String -> Aeson.Parser (Maybe a) | |
optional object key = object Aeson..:? Key.fromString key | |
withDefault :: a -> Aeson.Parser (Maybe a) -> Aeson.Parser a | |
withDefault = flip (Aeson..!=) | |
pair :: Aeson.ToJSON a => String -> a -> Aeson.Pair | |
pair key value = Key.fromString key Aeson..= value | |
field :: Csv.ToField b => String -> (a -> b) -> (Csv.Name, a -> Csv.Field) | |
field name f = (Text.encodeUtf8 $ Text.pack name, Csv.toField . f) |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
module HW_Section where | |
import qualified Data.Text as Text | |
import qualified Data.Vector as Vector | |
import qualified HW_Question as Question | |
import qualified Numeric.Natural as Natural | |
data Section = Section | |
{ index :: Natural.Natural, | |
title :: Text.Text, | |
questions :: Vector.Vector Question.Question | |
} | |
deriving (Eq, Show) | |
anchor :: Section -> Text.Text | |
anchor section = Text.pack $ "s" <> show (index section) |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
module HW_Singleton where | |
import qualified Data.Aeson as Aeson | |
import qualified Data.Csv as Csv | |
import qualified Data.Vector as Vector | |
newtype Singleton a = Singleton | |
{ unwrap :: a | |
} | |
deriving (Eq, Show) | |
instance Aeson.FromJSON a => Aeson.FromJSON (Singleton a) where | |
parseJSON = Aeson.withArray "Singleton" $ \xs -> case Vector.uncons xs of | |
Just (x, ys) | Vector.null ys -> Singleton <$> Aeson.parseJSON x | |
_ -> fail $ "expected singleton array but got " <> show xs | |
instance Aeson.ToJSON a => Aeson.ToJSON (Singleton a) where | |
toJSON = Aeson.toJSON . (: []) . unwrap | |
instance Csv.ToField a => Csv.ToField (Singleton a) where | |
toField = Csv.toField . unwrap |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
module HW_Survey where | |
import qualified Data.Text as Text | |
import qualified Data.Vector as Vector | |
import qualified HW_Answer as Answer | |
import qualified HW_Other as Other | |
import qualified HW_Question as Question | |
import qualified HW_Section as Section | |
import qualified Numeric.Natural as Natural | |
sections :: Vector.Vector Section.Section | |
sections = | |
Vector.fromList | |
[ section | |
10 | |
"Survey" | |
[ question 0 "When did you submit your survey response?" $ | |
single | |
[ "2022-11-01", | |
"2022-11-02", | |
"2022-11-03", | |
"2022-11-04", | |
"2022-11-05", | |
"2022-11-06", | |
"2022-11-07", | |
"2022-11-08", | |
"2022-11-09", | |
"2022-11-10", | |
"2022-11-11", | |
"2022-11-12", | |
"2022-11-13", | |
"2022-11-14", | |
"2022-11-15" | |
], | |
question 1 "Did you provide an email address?" $ | |
single | |
[ "No", | |
"Yes" | |
] | |
], | |
section | |
0 | |
"Haskell usage" | |
[ question 1 "Do you use Haskell?" $ | |
single | |
[ "Yes", | |
"No, but I used to", | |
"No, I never have" | |
], | |
question 2 "If you stopped using Haskell, how long did you use it before you stopped?" $ | |
single | |
[ "Less than 1 day", | |
"1 day to 1 week", | |
"1 week to 1 month", | |
"1 month to 1 year", | |
"More than 1 year" | |
], | |
question 3 "If you do not use Haskell, why not?" $ | |
multi | |
Other.Allow | |
[ "My company doesn't use Haskell", | |
"Haskell is too hard to learn", | |
"Haskell's documentation is not good enough", | |
"Haskell lacks critical libraries", | |
"Haskell lacks critical tools", | |
"Haskell's performance is not good enough", | |
"Haskell does not support the platforms I need", | |
"Haskell lacks critical features" | |
], | |
question 4 "How many years have you been using Haskell?" $ | |
single | |
[ "Less than 1", | |
"1 to 2", | |
"2 to 3", | |
"3 to 4", | |
"4 to 5", | |
"5 to 6", | |
"6 to 7", | |
"7 to 8", | |
"8 to 9", | |
"9 to 10", | |
"10 to 11", | |
"11 to 12", | |
"12 to 13", | |
"13 to 14", | |
"14 to 15", | |
"More than 15" | |
], | |
question 5 "How frequently do you use Haskell?" $ | |
single | |
[ "Daily", | |
"Weekly", | |
"Monthly", | |
"Yearly", | |
"Rarely" | |
], | |
question 6 "How would you rate your proficiency in Haskell?" $ | |
single | |
[ "I can't write or read Haskell", | |
"I can write simple programs in Haskell", | |
"I can write useful, production-ready code but it is a struggle", | |
"I am productive writing Haskell", | |
"I'm an expert" | |
], | |
question 7 "Where do you use Haskell?" $ | |
multi | |
Other.Forbid | |
[ "Home", | |
"Industry", | |
"Academia", | |
"School" | |
], | |
question 8 "Do you use Haskell at work?" $ | |
single | |
[ "Yes, most of the time", | |
"Yes, some of the time", | |
"No, but my company does", | |
"No, but I'd like to", | |
"No, and I don't want to" | |
], | |
question 9 "If you do not use Haskell at work, why not?" $ | |
multi | |
Other.Allow | |
[ "My company doesn't use Haskell", | |
"It's too hard to hire Haskell developers", | |
"Haskell is too hard to learn", | |
"Haskell lacks critical libraries", | |
"Haskell lacks critical tools", | |
"Haskell's documentation is not good enough", | |
"Haskell's performance is not good enough", | |
"Haskell does not support the platforms I need", | |
"Haskell lacks critical features" | |
], | |
question 10 "Which programming languages other than Haskell are you fluent in?" $ | |
multi | |
Other.Allow | |
[ "Python", | |
"C", | |
"JavaScript", | |
"Java", | |
"Shell", | |
"C++", | |
"TypeScript", | |
"Rust", | |
"Elm", | |
"C#", | |
"Scala", | |
"Go", | |
"PureScript", | |
"Ruby", | |
"PHP", | |
"Assembly", | |
"Ocaml", | |
"Clojure", | |
"Lua", | |
"R", | |
"Kotlin", | |
"Perl", | |
"Matlab", | |
"F#", | |
"Erlang", | |
"Swift", | |
"Elixir", | |
"Common Lisp", | |
"Nix", | |
"Prolog", | |
"Agda", | |
"Julia", | |
"Scheme", | |
"Idris", | |
"Ada", | |
"Pascal", | |
"Zig", | |
"Dart", | |
"Groovy", | |
"Haxe", | |
"Objective-C" | |
], | |
question 11 "Which types of software do you develop with Haskell?" $ | |
multi | |
Other.Allow | |
[ "Command-line programs (CLI)", | |
"API services (returning non-HTML)", | |
"Libraries or frameworks", | |
"Data processing", | |
"Automation or scripts", | |
"Web services (returning HTML)", | |
"Agents or daemons", | |
"Desktop programs (GUI)", | |
"Compilers", | |
"Games" | |
], | |
question 12 "Which industries do you use Haskell in?" $ | |
multi | |
Other.Allow | |
[ "Web", | |
"Academia", | |
"Banking or finance", | |
"Education", | |
"Science", | |
"Commerce or retail", | |
"Cryptocurrency", | |
"Gaming", | |
"Healthcare or medical", | |
"Embedded", | |
"Mobile", | |
"Government" | |
] | |
], | |
section | |
1 | |
"Projects" | |
[ question 0 "How many Haskell projects do you contribute to?" $ | |
single | |
[ "0", | |
"1", | |
"2", | |
"3", | |
"4", | |
"5", | |
"6 to 10", | |
"11 to 20", | |
"More than 20" | |
], | |
question 1 "What is the total size of all the Haskell projects you contribute to?" $ | |
single | |
[ "Less than 1,000 lines of code", | |
"Between 1,000 and 9,999 lines of code", | |
"Between 10,000 and 99,999 lines of code", | |
"More than 100,000 lines of code" | |
], | |
question 2 "Which platforms do you develop Haskell on?" $ | |
multi | |
Other.Allow | |
[ "Linux", | |
"MacOS", | |
"Windows", | |
"BSD", | |
"WSL" | |
], | |
question 3 "Which platforms do you target?" $ | |
multi | |
Other.Allow | |
[ "Linux", | |
"MacOS", | |
"Windows", | |
"BSD", | |
"Android", | |
"iOS", | |
"Web" | |
] | |
], | |
section | |
2 | |
"Compilers" | |
[ question 0 "Which Haskell compilers do you use?" $ | |
multi | |
Other.Allow | |
[ "GHC", | |
"GHCJS", | |
"Clash", | |
"Hugs", | |
"Mu" | |
], | |
question 1 "Which installation methods do you use for your Haskell compiler?" $ | |
multi | |
Other.Allow | |
[ "ghcup", | |
"Nix", | |
"Stack", | |
"Operating system package", | |
"Official binaries", | |
"Source", | |
"Haskell Platform", | |
"Homebrew", | |
"Chocolatey", | |
"Guix" | |
], | |
question 2 "Has upgrading your Haskell compiler broken your code in the last year?" $ | |
single | |
[ "No", | |
"Yes" | |
], | |
question 3 "How has upgrading your Haskell compiler broken your code in the last year?" $ | |
multi | |
Other.Allow | |
[ "Incompatible dependencies", | |
"Expected changes, such as the MonadFail proposal", | |
"New warnings", | |
"Compiler bugs", | |
"Unexpected changes", | |
"Simplified Subsumption" | |
], | |
question 4 "Which versions of GHC do you use?" $ | |
multi | |
Other.Forbid | |
[ "> 9.4", | |
"9.4", | |
"9.2", | |
"9.0", | |
"8.10.x", | |
"8.8.x", | |
"8.6.x", | |
"< 8.6" | |
], | |
question 5 "Which language extensions would you like to be enabled by default?" $ | |
extension | |
[ "AllowAmbiguousTypes", | |
"ApplicativeDo", | |
"Arrows", | |
"BangPatterns", | |
"BinaryLiterals", | |
"BlockArguments", | |
"CApiFFI", | |
"ConstrainedClassMethods", | |
"ConstraintKinds", | |
"Cpp", | |
"DataKinds", | |
"DatatypeContexts", | |
"DefaultSignatures", | |
"DeriveAnyClass", | |
"DeriveDataTypeable", | |
"DeriveFoldable", | |
"DeriveFunctor", | |
"DeriveGeneric", | |
"DeriveLift", | |
"DeriveTraversable", | |
"DerivingStrategies", | |
"DerivingVia", | |
"DisambiguateRecordFields", | |
"DuplicateRecordFields", | |
"EmptyCase", | |
"ExistentialQuantification", | |
"ExplicitForAll", | |
"ExplicitNamespaces", | |
"ExtendedDefaultRules", | |
"FlexibleContexts", | |
"FlexibleInstances", | |
"ForeignFunctionInterface", | |
"FunctionalDependencies", | |
"GADTs", | |
"GADTSyntax", | |
"GeneralizedNewtypeDeriving", | |
"HexFloatLiterals", | |
"ImplicitParams", | |
"ImportQualifiedPost", | |
"ImpredicativeTypes", | |
"IncoherentInstances", | |
"InstanceSigs", | |
"InterruptibleFFI", | |
"KindSignatures", | |
"LambdaCase", | |
"LiberalTypeSynonyms", | |
"LinearTypes", | |
"MagicHash", | |
"MonadComprehensions", | |
"MonoLocalBinds", | |
"MultiParamTypeClasses", | |
"MultiWayIf", | |
"NamedFieldPuns", | |
"NamedWildCards", | |
"NegativeLiterals", | |
"NoEmptyDataDecls", | |
"NoFieldSelectors", | |
"NoImplicitPrelude", | |
"NoMonadFailDesugaring", | |
"NoMonomorphismRestriction", | |
"NoPatternGuards", | |
"NoStarIsType", | |
"NoTraditionalRecordSyntax", | |
"NPlusKPatterns", | |
"NullaryTypeClasses", | |
"NumDecimals", | |
"NumericUnderscores", | |
"OverlappingInstances", | |
"OverloadedLabels", | |
"OverloadedLists", | |
"OverloadedRecordDot", | |
"OverloadedRecordUpdate", | |
"OverloadedStrings", | |
"PackageImports", | |
"ParallelListComp", | |
"PartialTypeSignatures", | |
"PatternSynonyms", | |
"PolyKinds", | |
"PostfixOperators", | |
"QuantifiedConstraints", | |
"QuasiQuotes", | |
"Rank2Types", | |
"RankNTypes", | |
"RebindableSyntax", | |
"RecordWildCards", | |
"RecursiveDo", | |
"RoleAnnotations", | |
"ScopedTypeVariables", | |
"StandaloneDeriving", | |
"StandaloneKindSignatures", | |
"StaticPointers", | |
"Strict", | |
"StrictData", | |
"TemplateHaskell", | |
"TemplateHaskellQuotes", | |
"TransformListComp", | |
"Trustworthy", | |
"TupleSections", | |
"TypeApplications", | |
"TypeFamilies", | |
"TypeFamilyDependencies", | |
"TypeInType", | |
"TypeOperators", | |
"TypeSynonymInstances", | |
"UnboxedSums", | |
"UnboxedTuples", | |
"UndecidableInstances", | |
"UndecidableSuperClasses", | |
"UnicodeSyntax", | |
"UnliftedDatatypes", | |
"UnliftedNewtypes", | |
"Unsafe", | |
"ViewPatterns" | |
], | |
question 6 "How important do you feel it would be to have a new version of the Haskell language standard?" $ | |
single | |
[ "Extremely important", | |
"Very important", | |
"Moderately important", | |
"Slightly important", | |
"Not at all important" | |
] | |
], | |
section | |
3 | |
"Tooling" | |
[ question 0 "Which build tools do you use for Haskell?" $ | |
multi | |
Other.Allow | |
[ "Cabal", | |
"Stack", | |
"Nix", | |
"haskell.nix", | |
"Make", | |
"Shake", | |
"ghc-pkg", | |
"Bazel", | |
"Guix" | |
], | |
question 1 "Which editors do you use for Haskell?" $ | |
multi | |
Other.Allow | |
[ "Visual Studio Code", | |
"Vi family", | |
"Emacs family", | |
"IntelliJ IDEA", | |
"Sublime Text", | |
"Atom", | |
"Kakoune", | |
"Helix", | |
"Notepad++", | |
"Geany" | |
], | |
question 2 "Which IDEs do you use for Haskell?" $ | |
multi | |
Other.Allow | |
[ "Haskell Language Server (HLS)", | |
"ghcid", | |
"IntelliJ", | |
"ghcide", | |
"Intero", | |
"Dante", | |
"GHCi" | |
], | |
question 3 "Which version control systems do you use for Haskell?" $ | |
multi | |
Other.Allow | |
[ "Git", | |
"Darcs", | |
"Mercurial", | |
"Fossil", | |
"Pijul" | |
], | |
question 4 "Where do you get Haskell packages from?" $ | |
multi | |
Other.Allow | |
[ "Hackage", | |
"Stackage", | |
"Nix", | |
"Source" | |
], | |
question 5 "Which tools do you use to test Haskell code?" $ | |
multi | |
Other.Allow | |
[ "QuickCheck", | |
"Hspec", | |
"Tasty", | |
"HUnit", | |
"Hedgehog", | |
"SmallCheck", | |
"Haskell Test Framework", | |
"doctest" | |
], | |
question 6 "Which tools do you use to benchmark Haskell code?" $ | |
multi | |
Other.Allow | |
[ "Criterion", | |
"tasty-bench", | |
"Bench", | |
"Gauge" | |
] | |
], | |
section | |
4 | |
"Infrastructure" | |
[ question 0 "Which tools do you use to deploy Haskell applications?" $ | |
multi | |
Other.Allow | |
[ "Static binaries", | |
"Docker images", | |
"Nix expressions", | |
"Dynamic binaries" | |
], | |
question 1 "Where do you deploy Haskell applications?" $ | |
multi | |
Other.Allow | |
[ "Self or company owned servers", | |
"Amazon Web Services", | |
"Google Cloud", | |
"Digital Ocean", | |
"Heroku", | |
"Microsoft Azure", | |
"Linode", | |
"Hetzner" | |
] | |
], | |
section | |
5 | |
"Community" | |
[ question 0 "Where do you interact with the Haskell community?" $ | |
multi | |
Other.Allow | |
[ "Reddit", | |
"GitHub", | |
"Twitter", | |
"Stack Overflow", | |
"Discord", | |
"IRC", | |
"Mailing lists", | |
"Discourse", | |
"Conferences (academic)", | |
"Conferences (commercial)", | |
"Slack", | |
"Telegram", | |
"Meetups", | |
"Matrix/Riot", | |
"Lobsters", | |
"Mastodon", | |
"Zulip", | |
"Gitter", | |
"Cohost", | |
"Hacker News" | |
], | |
question 1 "Which of the following Haskell topics would you like to see more written about?" $ | |
multi | |
Other.Allow | |
[ "Best practices", | |
"Design patterns", | |
"Application architectures", | |
"Performance analysis", | |
"Debugging how-tos", | |
"Production infrastructure", | |
"Library walkthroughs", | |
"Tooling choices", | |
"Case studies", | |
"Algorithm implementations", | |
"Project maintenance", | |
"Web development", | |
"GUIs", | |
"Testing", | |
"Project setup", | |
"Beginner fundamentals", | |
"Machine learning", | |
"Game development", | |
"Mobile development", | |
"Comparisons to other languages" | |
] | |
], | |
section | |
6 | |
"Feelings" | |
[ question 19 "I would prefer to use Haskell for my next new project." likert, | |
question 18 "I would recommend using Haskell to others." likert, | |
question 1 "I am satisfied with Haskell as a language." likert, | |
question 14 "Once my Haskell program compiles, it generally does what I intended." likert, | |
question 13 "I think that software written in Haskell is easy to maintain." likert, | |
question 2 "I am satisfied with Haskell's compilers, such as GHC." likert, | |
question 0 "I feel welcome in the Haskell community." likert, | |
question 16 "Haskell's performance meets my needs." likert, | |
question 4 "I am satisfied with Haskell's package repositories, such as Hackage." likert, | |
question 6 "I think Haskell libraries are high quality." likert, | |
question 15 "I think that Haskell libraries perform well." likert, | |
question 20 "Haskell is working well for my team." likert, | |
question 5 "I can find Haskell libraries for the things that I need." likert, | |
question 12 "I think that Haskell libraries work well together." likert, | |
question 11 "I think that Haskell libraries provide a stable API." likert, | |
question 3 "I am satisfied with Haskell's build tools, such as Cabal." likert, | |
question 21 "Haskell is critical to my company's success." likert, | |
question 7 "I have a good understanding of Haskell best practices." likert, | |
question 10 "I think that Haskell libraries are easy to use." likert, | |
question 23 "As a hiring manager, I can easily find qualified Haskell candidates." likert, | |
question 8 "I think Haskell libraries are well documented." likert, | |
question 9 "I can easily compare competing Haskell libraries to select the best one." likert, | |
question 22 "As a candidate, I can easily find Haskell jobs." likert, | |
question 17 "I can easily reason about the performance of my Haskell code." likert | |
], | |
section | |
7 | |
"Demographics" | |
[ question 0 "Which country do you live in?" $ | |
single | |
[ "United States", | |
"Germany", | |
"United Kingdom", | |
"Russia", | |
"Netherlands", | |
"Australia", | |
"Canada", | |
"France", | |
"Sweden", | |
"Poland", | |
"India", | |
"Brazil", | |
"Japan", | |
"Austria", | |
"Switzerland", | |
"Czech Republic", | |
"Finland", | |
"Italy", | |
"China", | |
"Spain", | |
"Norway", | |
"Ukraine", | |
"Bulgaria", | |
"Belgium", | |
"Denmark", | |
"Argentina", | |
"Portugal", | |
"Singapore", | |
"Taiwan", | |
"Armenia", | |
"Israel", | |
"Mexico", | |
"Lithuania", | |
"Serbia and Montenegro", | |
"Belarus", | |
"Croatia", | |
"Estonia", | |
"Georgia", | |
"Ireland", | |
"New Zealand", | |
"Romania", | |
"South Africa", | |
"South Korea", | |
"Chile", | |
"Colombia", | |
"Ecuador", | |
"Hungary", | |
"Indonesia", | |
"Iran", | |
"Iraq", | |
"Kazakhstan", | |
"Latvia", | |
"Slovakia", | |
"Thailand", | |
"Turkey", | |
"Cyprus", | |
"Greece", | |
"Isle of Man", | |
"Kenya", | |
"Kyrgyzstan", | |
"Luxembourg", | |
"Nepal", | |
"United Arab Emirates", | |
"Uruguay", | |
"Vietnam" | |
], | |
question 1 "Do you consider yourself a member of an underrepresented or marginalized group in technology?" $ | |
multi | |
Other.Allow | |
[ "Lesbian, gay, bisexual, queer or otherwise non-heterosexual", | |
"Disabled or person with disability (including physical, mental, and other)", | |
"Political beliefs", | |
"Older or younger than the average developers I know", | |
"Racial or ethnic minority", | |
"Trans", | |
"Woman or perceived as a woman", | |
"Yes, but I prefer not to say which", | |
"Non-binary gender", | |
"Educational background", | |
"Religious beliefs", | |
"Cultural beliefs", | |
"Language" | |
], | |
question 2 "Do you feel your belonging to an underrepresented or marginalized group in technology makes it difficult for you to participate in the Haskell community?" $ | |
single | |
[ "Never", | |
"Sometimes", | |
"Often" | |
], | |
question 3 "Are you a student?" $ | |
single | |
[ "No", | |
"Yes, full time", | |
"Yes, part time" | |
], | |
question 4 "What is the highest level of education you have completed?" $ | |
single | |
[ "Less than high school diploma", | |
"High school diploma", | |
"Some college", | |
"Associate degree", | |
"Bachelor's degree", | |
"Master's degree", | |
"Professional degree", | |
"Doctoral degree" | |
], | |
question 5 "What is your employment status?" $ | |
single | |
[ "Employed full time", | |
"Employed part time", | |
"Self employed", | |
"Not employed, and not looking for work", | |
"Not employed, but looking for work", | |
"Retired" | |
], | |
question 6 "How large is the company you work for?" $ | |
single | |
[ "Fewer than 10 employees", | |
"10 to 99 employees", | |
"100 to 999 employees", | |
"More than 1,000 employees" | |
], | |
question 7 "How many years have you been coding?" $ | |
single | |
[ "0 to 4 years", | |
"5 to 9 years", | |
"10 to 14 years", | |
"15 to 19 years", | |
"20 to 24 years", | |
"25 to 29 years", | |
"30 or more years" | |
], | |
question 8 "How many years have you been coding professionally?" $ | |
single | |
[ "0 to 4 years", | |
"5 to 9 years", | |
"10 to 14 years", | |
"15 to 19 years", | |
"20 to 24 years", | |
"25 to 29 years", | |
"30 or more years" | |
], | |
question 9 "Do you code as a hobby?" $ | |
single | |
[ "Yes", | |
"No" | |
], | |
question 10 "Have you contributed to any open source projects?" $ | |
single | |
[ "Yes", | |
"No" | |
] | |
], | |
section | |
8 | |
"Meta" | |
[ question 0 "Did you take any previous surveys?" $ | |
multi | |
Other.Forbid | |
[ "2021", | |
"2020", | |
"2019", | |
"2018", | |
"2017" | |
], | |
question 1 "How did you hear about this survey?" $ | |
multi | |
Other.Allow | |
[ "Reddit", | |
"Haskell Weekly", | |
"Twitter", | |
"Slack", | |
"Mailing lists", | |
"Telegram", | |
"Discourse", | |
"Hacker News", | |
"Lobsters", | |
"In person", | |
"Discord", | |
"Mastodon", | |
"IRC", | |
"Cohost", | |
"Matrix/Riot", | |
"GitHub" | |
] | |
], | |
section | |
9 | |
"Free response" | |
[ question 0 "If you wanted to convince someone to use Haskell, what would you say?" Answer.Free, | |
question 1 "If you could change one thing about Haskell, what would it be?" Answer.Free | |
] | |
] | |
section :: Natural.Natural -> String -> [Question.Question] -> Section.Section | |
section index title questions = | |
Section.Section | |
{ Section.index = index, | |
Section.title = Text.pack title, | |
Section.questions = Vector.fromList questions | |
} | |
question :: Natural.Natural -> String -> Answer.Answer -> Question.Question | |
question index prompt answer = | |
Question.Question | |
{ Question.index = index, | |
Question.prompt = Text.pack prompt, | |
Question.answer = answer | |
} | |
single :: [String] -> Answer.Answer | |
single = Answer.Single . Vector.fromList . fmap Text.pack | |
multi :: Other.Other -> [String] -> Answer.Answer | |
multi other = Answer.Multi other . Vector.fromList . fmap Text.pack | |
extension :: [String] -> Answer.Answer | |
extension = Answer.Extension . Vector.fromList . fmap Text.pack | |
likert :: Answer.Answer | |
likert = | |
Answer.Single . Vector.fromList $ | |
fmap | |
Text.pack | |
[ " Strongly agree", | |
"Agree", | |
"Neutral", | |
"Disagree", | |
"Strongly disagree" | |
] |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
module HW_Timestamp where | |
import qualified Data.Aeson as Aeson | |
import qualified Data.Csv as Csv | |
import qualified Data.Time as Time | |
newtype Timestamp = Timestamp | |
{ unwrap :: Time.UTCTime | |
} | |
deriving (Eq, Show) | |
instance Aeson.FromJSON Timestamp where | |
parseJSON = fmap Timestamp . Aeson.parseJSON | |
instance Aeson.ToJSON Timestamp where | |
toJSON = Aeson.toJSON . unwrap | |
instance Csv.ToField Timestamp where | |
toField = Csv.toField . Time.formatTime Time.defaultTimeLocale "%Y-%m-%dT%H:%M:%SZ" . unwrap |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
cabal-version: >=1.10 | |
name: survey | |
version: 2022 | |
build-type: Simple | |
executable survey | |
build-depends: | |
aeson | |
, aeson-pretty | |
, base | |
, bytestring | |
, case-insensitive | |
, cassava | |
, containers | |
, directory | |
, filepath | |
, lucid | |
, text | |
, time | |
, vector | |
default-language: Haskell2010 | |
ghc-options: | |
-Weverything -Wno-all-missed-specialisations -Wno-implicit-prelude | |
-Wno-missing-deriving-strategies -Wno-missing-export-lists | |
-Wno-missing-kind-signatures -Wno-missing-safe-haskell-mode | |
-Wno-prepositive-qualified-module -Wno-safe -Wno-unsafe | |
main-is: HW_Main.hs | |
other-modules: | |
HW_Answer | |
HW_Bag | |
HW_Choice | |
HW_Other | |
HW_Question | |
HW_Response | |
HW_Section | |
HW_Singleton | |
HW_Survey | |
HW_Timestamp |
Sign up for free
to join this conversation on GitHub.
Already have an account?
Sign in to comment