Skip to content

Commit 3aed93f

Browse files
MarcosJLRsjakobi
andauthored
Feature/dhall csv docs (#2279)
* feat(dhall-to-csv): reference documentation * feat(dhall-to-csv): better error messages * feat(csv-to-dhall): reference documentacion * feat(csv-to-dhall): improved error messages * feat(csv-to-dhall): fixed an extra pattern * feat(dhall-csv): docs for dhall csv utilities * feat(dhall-csv): add ci verification for haddock * feat(dhall-csv): removed ci verification for haddock * Update dhall-csv/src/Dhall/Csv.hs Co-authored-by: Simon Jakobi <simon.jakobi@gmail.com> * Update dhall-csv/src/Dhall/Csv.hs Co-authored-by: Simon Jakobi <simon.jakobi@gmail.com> * Update dhall-csv/src/Dhall/Csv.hs Co-authored-by: Simon Jakobi <simon.jakobi@gmail.com> * Update dhall-csv/src/Dhall/CsvToDhall.hs Co-authored-by: Simon Jakobi <simon.jakobi@gmail.com> * Update dhall-csv/src/Dhall/CsvToDhall.hs Co-authored-by: Simon Jakobi <simon.jakobi@gmail.com> * fix(dhall-csv): use display exception instead of show * fix(dhall-csv): typos and other minor mistakes * feat(dhall-csv): include types in error messages * fix(dhall-csv): minor fixes in error messages * fix(dhall-csv): typo Co-authored-by: Simon Jakobi <simon.jakobi@gmail.com>
1 parent 75d2822 commit 3aed93f

File tree

3 files changed

+535
-74
lines changed

3 files changed

+535
-74
lines changed

dhall-csv/src/Dhall/Csv.hs

Lines changed: 181 additions & 18 deletions
Original file line numberDiff line numberDiff line change
@@ -1,12 +1,91 @@
11
{-#LANGUAGE OverloadedStrings#-}
22

3+
{-| This library exports two functions: `dhallToCsv` and `codeToValue`.
4+
The former converts a Dhall expression (with imports resolved already) into a
5+
sequence of CSV `NamedRecord`s (from the @cassava@ library) while the latter
6+
converts a `Text` containing Dhall code into a list of CSV `NamedRecord`s.
7+
8+
Not all Dhall expressions can be converted to CSV since CSV is not a
9+
programming language. The only things you can convert are @List@s of
10+
records where each field is one of the following types:
11+
12+
* @Bool@s
13+
* @Natural@s
14+
* @Integer@s
15+
* @Double@s
16+
* @Text@ values
17+
* @Optional@ (of valid field types)
18+
* unions (of empty alternatives or valid record field types)
19+
20+
Dhall @Bool@s translate to either `"true"` or `"false"` in all lowercase letters:
21+
22+
> $ dhall-to-csv <<< '[{ exampleBool = True }]'
23+
> exampleBool
24+
> true
25+
> $ dhall-to-csv <<< '[{ exampleBool = False }]'
26+
> exampleBool
27+
> false
28+
29+
Dhall numbers translate to their string representations:
30+
31+
> $ dhall-to-csv <<< '[{ exampleInteger = +2 }]'
32+
> exampleInteger
33+
> 2
34+
> $ dhall-to-csv <<< '[{ exampleNatural = 2 }]'
35+
> exampleNatural
36+
> 2
37+
> $ dhall-to-csv <<< '[{ exampleDouble = 2.3 }]'
38+
> exampleDouble
39+
> 2.3
40+
41+
Dhall @Text@ translates directly to CSV. Special CSV characters
42+
are enclosed by double quotes:
43+
44+
> $ dhall-to-csv <<< '[{ exampleText = "ABC" }]'
45+
> exampleText
46+
> ABC
47+
> $ dhall-to-csv <<< '[{ exampleText = "ABC,ABC" }]'
48+
> exampleText
49+
> "ABC,ABC"
50+
51+
Dhall @Optional@ values translate to the empty string if absent and the unwrapped
52+
value otherwise:
53+
54+
> $ dhall-to-csv <<< '[{ exampleOptional = None Natural }]'
55+
> exampleOptional
56+
>
57+
> $ dhall-to-csv <<< '[{ exampleOptional = Some 1 }]'
58+
> exampleOptional
59+
> 1
60+
61+
Dhall unions translate to the wrapped value or the name of the field
62+
(in case it is an empty field):
63+
64+
> $ dhall-to-csv <<< "[{ exampleUnion = < Left | Right : Natural>.Left }]"
65+
> exampleUnion
66+
> Left
67+
> $ dhall-to-csv <<< "[{ exampleUnion = < Left | Right : Natural>.Right 2 }]"
68+
> exampleUnion
69+
> 2
70+
71+
Also, all Dhall expressions are normalized before translation to CSV:
72+
73+
> $ dhall-to-csv <<< "[{ equality = True == False }]"
74+
> equality
75+
> false
76+
-}
77+
378
module Dhall.Csv (
479
dhallToCsv
580
, codeToValue
81+
82+
-- * Exceptions
83+
, CompileError
684
) where
785

8-
import Control.Exception (Exception, throwIO)
9-
import Data.Csv (ToField (..))
86+
import Control.Exception (Exception, throwIO, displayException)
87+
import Data.Csv (NamedRecord, ToField (..))
88+
import Data.Either (fromRight)
1089
import Data.Maybe (fromMaybe)
1190
import Data.Sequence (Seq)
1291
import Data.Text (Text)
@@ -25,42 +104,123 @@ import qualified Dhall.Import
25104
import qualified Dhall.Map
26105
import qualified Dhall.Parser
27106
import qualified Dhall.Pretty
28-
import qualified Dhall.TypeCheck
107+
import qualified Dhall.TypeCheck as TypeCheck
29108
import qualified Dhall.Util
30109
import qualified System.FilePath
31110

32-
data CompileError = Unsupported (Expr Void Void)
111+
{-| This is the exception type for errors that can arise when converting from
112+
Dhall to CSV.
113+
114+
It contains information on the specific cases that might
115+
fail to give a better insight.
116+
-}
117+
data CompileError
118+
= Unsupported (Expr Void Void)
119+
| NotAList (Expr Void Void)
120+
| NotARecord (Expr Void Void)
121+
| BareNone
122+
deriving (Show)
33123

34-
instance Show CompileError where
35-
show (Unsupported e) =
124+
instance Exception CompileError where
125+
displayException (Unsupported e) =
36126
Data.Text.unpack $
37-
_ERROR <> ": Cannot translate to CSV \n\
127+
_ERROR <> ": Cannot translate record field to CSV \n\
38128
\ \n\
39-
\Explanation: Only records of primitive values can be \n\
40-
\translated from Dhall to CSV. \n\
129+
\Explanation: Only the following types of record fields can be converted to CSV: \n\
130+
\ \n\
131+
\● ❰Bool❱ \n\
132+
\● ❰Natural❱ \n\
133+
\● ❰Integer❱ \n\
134+
\● ❰Double❱ \n\
135+
\● ❰Text❱ \n\
136+
\● ❰Optional t❱ (where ❰t❱ is a valid record field type) \n\
137+
\● Unions * \n\
138+
\ \n\
139+
\* Unions can have empty alternatives or alternatives with valid \n\
140+
\ record field types \n\
41141
\ \n\
42142
\The following Dhall expression could not be translated to CSV: \n\
43143
\ \n\
44-
\" <> insert e
144+
\" <> insert e <> "\n\
145+
\ \n\
146+
\... because it has type: \n\
147+
\ \n\
148+
\" <> insert (fromRight e (TypeCheck.typeOf e))
149+
150+
displayException (NotAList e) =
151+
Data.Text.unpack $
152+
_ERROR <> ": Top level object must be of type ❰List❱ \n\
153+
\ \n\
154+
\Explanation: To translate to CSV you must provide a list of records. \n\
155+
\Other types can not be translated directly. \n\
156+
\ \n\
157+
\Expected an expression of type List {...} but instead got the following \n\
158+
\expression: \n\
159+
\ \n\
160+
\" <> insert e <> "\n\
161+
\ \n\
162+
\... which has type: \n\
163+
\ \n\
164+
\" <> insert (fromRight e (TypeCheck.typeOf e))
165+
166+
displayException (NotARecord e) =
167+
Data.Text.unpack $
168+
_ERROR <> ": Elements of the top-level list must be records \n\
169+
\ \n\
170+
\Explanation: To translate to CSV you must provide a list of records. \n\
171+
\Other types can not be translated directly. \n\
172+
\ \n\
173+
\Expected a record but instead got the following expression: \n\
174+
\ \n\
175+
\" <> insert e <> "\n\
176+
\ \n\
177+
\... which has type: \n\
178+
\ \n\
179+
\" <> insert (fromRight e (TypeCheck.typeOf e))
45180

46-
instance Exception CompileError
181+
displayException BareNone =
182+
Data.Text.unpack $
183+
_ERROR <> ": ❰None❱ is not valid on its own \n\
184+
\ \n\
185+
\Explanation: The conversion to CSV does not accept ❰None❱ in isolation as a \n\
186+
\valid way to represent a null value. In Dhall, ❰None❱ is a function whose \n\
187+
\input is a type and whose output is an ❰Optional❱ of that type. \n\
188+
\ \n\
189+
\For example: \n\
190+
\ \n\
191+
\ \n\
192+
\ ┌─────────────────────────────────┐ ❰None❱ is a function whose result is \n\
193+
\ │ None : ∀(a : Type) → Optional a │ an ❰Optional❱ value, but the function \n\
194+
\ └─────────────────────────────────┘ itself is not a valid ❰Optional❱ value \n\
195+
\ \n\
196+
\ \n\
197+
\ ┌─────────────────────────────────┐ ❰None Natural❱ is a valid ❰Optional❱ \n\
198+
\ │ None Natural : Optional Natural │ value (an absent ❰Natural❱ number in \n\
199+
\ └─────────────────────────────────┘ this case) \n\
200+
\ \n\
201+
\ \n\
202+
\ \n\
203+
\The conversion to CSV only translates the fully applied form to empty string. "
47204

48205
insert :: Pretty a => a -> Text
49206
insert = Pretty.renderStrict . Dhall.Pretty.layout . Dhall.Util.insert
50207

208+
{-| Convert a Dhall expression (with resolved imports) to an
209+
sequence of CSV @NamedRecord@s.
210+
-}
51211
dhallToCsv
52212
:: Expr s Void
53-
-> Either CompileError (Seq Data.Csv.NamedRecord)
213+
-> Either CompileError (Seq NamedRecord)
54214
dhallToCsv e0 = listConvert $ Core.normalize e0
55215
where
56-
listConvert :: Expr Void Void -> Either CompileError (Seq Data.Csv.NamedRecord)
216+
listConvert :: Expr Void Void -> Either CompileError (Seq NamedRecord)
57217
listConvert (Core.ListLit _ a) = traverse recordConvert a
58-
listConvert e = Left $ Unsupported e
59-
recordConvert :: Expr Void Void -> Either CompileError Data.Csv.NamedRecord
218+
listConvert e = Left $ NotAList e
219+
recordConvert :: Expr Void Void -> Either CompileError NamedRecord
60220
recordConvert (Core.RecordLit a) = do
61221
a' <- traverse (fieldConvert . Core.recordFieldValue) a
62222
return $ Data.Csv.toNamedRecord $ Dhall.Map.toMap a'
63-
recordConvert e = Left $ Unsupported e
223+
recordConvert e = Left $ NotARecord e
64224
fieldConvert :: Expr Void Void -> Either CompileError Data.Csv.Field
65225
fieldConvert (Core.BoolLit True) = return $ toField ("true" :: Text)
66226
fieldConvert (Core.BoolLit False) = return $ toField ("false" :: Text)
@@ -72,12 +232,15 @@ dhallToCsv e0 = listConvert $ Core.normalize e0
72232
fieldConvert (Core.Field (Core.Union _) (Core.FieldSelection _ k _)) = return $ toField k
73233
fieldConvert (Core.Some e) = fieldConvert e
74234
fieldConvert (Core.App Core.None _) = return $ toField ("" :: Text)
235+
fieldConvert Core.None = Left BareNone
75236
fieldConvert e = Left $ Unsupported e
76237

238+
{-| Convert a @Text@ with Dhall code to a list of @NamedRecord@s.
239+
-}
77240
codeToValue
78241
:: Maybe FilePath
79242
-> Text
80-
-> IO [Data.Csv.NamedRecord]
243+
-> IO [NamedRecord]
81244
codeToValue mFilePath code = do
82245
parsedExpression <- Core.throws (Dhall.Parser.exprFromText (fromMaybe "(input)" mFilePath) code)
83246

@@ -87,7 +250,7 @@ codeToValue mFilePath code = do
87250

88251
resolvedExpression <- Dhall.Import.loadRelativeTo rootDirectory UseSemanticCache parsedExpression
89252

90-
_ <- Core.throws (Dhall.TypeCheck.typeOf resolvedExpression)
253+
_ <- Core.throws (TypeCheck.typeOf resolvedExpression)
91254

92255
case dhallToCsv resolvedExpression of
93256
Left err -> throwIO err

dhall-csv/src/Dhall/Csv/Util.hs

Lines changed: 11 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -4,6 +4,7 @@ module Dhall.Csv.Util (encodeCsvDefault, decodeCsvDefault) where
44

55
import Data.List (sort)
66
import Data.Text (Text)
7+
import Data.Csv (NamedRecord, Record)
78

89
import qualified Data.ByteString.Lazy as ByteString
910
import qualified Data.ByteString.Lazy.Char8 as ByteString.Char8
@@ -12,29 +13,34 @@ import qualified Data.HashMap.Strict as HashMap
1213
import qualified Data.Text.Encoding
1314
import qualified Data.Vector as Vector
1415

15-
encodeCsvDefault :: [Data.Csv.NamedRecord] -> Text
16+
{-| Utility to convert a list of @NamedRecord@ to Text formatted as a CSV.
17+
-}
18+
encodeCsvDefault :: [NamedRecord] -> Text
1619
encodeCsvDefault csv = Data.Text.Encoding.decodeUtf8 $ ByteString.toStrict $ Data.Csv.encodeByName header csv
1720
where
1821
header = case csv of
1922
[] -> Vector.empty
2023
(m:_) -> Vector.fromList $ sort $ HashMap.keys m
2124

22-
decodeCsvDefault :: Bool -> Text -> Either String [Data.Csv.NamedRecord]
25+
{-| Utility to decode a CSV into a list of records.
26+
Must specify whether the CSV to decode has header or not.
27+
-}
28+
decodeCsvDefault :: Bool -> Text -> Either String [NamedRecord]
2329
decodeCsvDefault hasHeader
2430
| hasHeader = decodeCsvWithHeader
2531
| otherwise = decodeCsvNoHeader
2632

27-
decodeCsvWithHeader :: Text -> Either String [Data.Csv.NamedRecord]
33+
decodeCsvWithHeader :: Text -> Either String [NamedRecord]
2834
decodeCsvWithHeader txt = do
2935
(_, vec) <- Data.Csv.decodeByName $ ByteString.fromStrict $ Data.Text.Encoding.encodeUtf8 txt
3036
return $ Vector.toList vec
3137

32-
decodeCsvNoHeader :: Text -> Either String [Data.Csv.NamedRecord]
38+
decodeCsvNoHeader :: Text -> Either String [NamedRecord]
3339
decodeCsvNoHeader txt = do
3440
vec <- Data.Csv.decode Data.Csv.NoHeader $ ByteString.fromStrict $ Data.Text.Encoding.encodeUtf8 txt
3541
return $ map addDefaultHeader $ Vector.toList vec
3642

37-
addDefaultHeader :: Data.Csv.Record -> Data.Csv.NamedRecord
43+
addDefaultHeader :: Record -> NamedRecord
3844
addDefaultHeader = HashMap.fromList . (zip headerBS) . Vector.toList
3945
where
4046
header = map (('_' :) . show) ([1..] :: [Int])

0 commit comments

Comments
 (0)