Skip to content
Merged
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
13 changes: 13 additions & 0 deletions dhall/src/Dhall/TH.hs
Original file line number Diff line number Diff line change
Expand Up @@ -47,6 +47,7 @@ import qualified Data.List as List
import qualified Data.Map as Map
import qualified Data.Set as Set
import qualified Data.Text as Text
import qualified Data.Time as Time
import qualified Data.Typeable as Typeable
import qualified Dhall
import qualified Dhall.Core as Core
Expand Down Expand Up @@ -145,6 +146,9 @@ toNestedHaskellType typeParams haskellTypes = loop
, "• ❰Integer❱ \n"
, "• ❰Natural❱ \n"
, "• ❰Text❱ \n"
, "• ❰Date❱ \n"
, "• ❰TimeOfDay❱ \n"
, "• ❰TimeZone❱ \n"
, "• ❰List a❱ (where ❰a❱ is also a valid nested type) \n"
, "• ❰Optional a❱ (where ❰a❱ is also a valid nested type) \n"
, "• Another matching datatype declaration \n"
Expand Down Expand Up @@ -175,6 +179,15 @@ toNestedHaskellType typeParams haskellTypes = loop
Text ->
return (ConT ''Text)

Date ->
return (ConT ''Time.Day)

Time ->
return (ConT ''Time.TimeOfDay)

TimeZone ->
return (ConT ''Time.TimeZone)

App List dhallElementType -> do
haskellElementType <- loop dhallElementType

Expand Down
15 changes: 15 additions & 0 deletions dhall/tests/Dhall/Test/TH.hs
Original file line number Diff line number Diff line change
Expand Up @@ -10,6 +10,7 @@ module Dhall.Test.TH where

import Control.Exception (throwIO)
import Data.Either.Validation (Validation (..))
import Data.Time (TimeOfDay (..), TimeZone (..), fromGregorian)
import Dhall.TH (HaskellType (..))
import Test.Tasty (TestTree)

Expand All @@ -27,6 +28,7 @@ deriving instance Show T
Dhall.TH.makeHaskellTypes
[ MultipleConstructors "Department" "./tests/th/Department.dhall"
, SingleConstructor "Employee" "MakeEmployee" "./tests/th/Employee.dhall"
, SingleConstructor "TimeExample" "TimeExample" "./tests/th/Time.dhall"
]

deriving instance Eq Department
Expand All @@ -35,6 +37,9 @@ deriving instance Show Department
deriving instance Eq Employee
deriving instance Show Employee

deriving instance Eq TimeExample
deriving instance Show TimeExample

Dhall.TH.makeHaskellTypes
[ SingleConstructor "Bar" "MakeBar" "(./tests/th/issue2066.dhall).Bar"
, SingleConstructor "Foo" "MakeFoo" "(./tests/th/issue2066.dhall).Foo"
Expand Down Expand Up @@ -75,6 +80,16 @@ makeHaskellTypeFromUnion = Tasty.HUnit.testCase "makeHaskellTypeFromUnion" $ do

Tasty.HUnit.assertEqual "" qux (Foo MakeFoo{ foo = 2, bar = MakeBar{ baz = 3 } })

timex <- Dhall.input Dhall.auto "let T = ./tests/th/Time.dhall in { txTime = 21:12:00, txDate = 1976-04-01, txTimeZone = +05:00 } : T"

Tasty.HUnit.assertEqual "" timex TimeExample { txTime = tod, txDate = day, txTimeZone = tz}

where
tod = TimeOfDay { todHour = 21, todMin = 12, todSec = 0 }
day = fromGregorian 1976 4 1
tz = TimeZone { timeZoneMinutes = 300, timeZoneSummerOnly = False, timeZoneName = "" }


Dhall.TH.makeHaskellTypesWith (Dhall.TH.defaultGenerateOptions
{ Dhall.TH.constructorModifier = ("My" <>)
, Dhall.TH.fieldModifier = ("my" <>) . Data.Text.toTitle
Expand Down
1 change: 1 addition & 0 deletions dhall/tests/th/Time.dhall
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
{ txTime : Time, txDate : Date, txTimeZone : TimeZone }