6
6
-- of patent rights can be found in the PATENTS file in the same directory.
7
7
8
8
9
-
10
- {-# LANGUAGE ExistentialQuantification #-}
11
- {-# LANGUAGE FlexibleInstances #-}
12
9
{-# LANGUAGE GADTs #-}
13
10
{-# LANGUAGE NoRebindableSyntax #-}
14
- {-# LANGUAGE TypeOperators #-}
15
11
16
12
17
13
module Duckling.Dimensions.Types
@@ -22,99 +18,14 @@ module Duckling.Dimensions.Types
22
18
, toName
23
19
) where
24
20
25
- import Data.GADT.Compare
26
- import Data.GADT.Show
27
- import Data.Hashable
28
- import qualified Data.HashMap.Strict as HashMap
29
21
import Data.Maybe
30
22
import Data.Some
31
23
import Data.Text (Text )
32
- -- Intentionally limit use of Typeable to avoid casting or typeOf usage
33
- import Data.Typeable ((:~:) (.. ))
34
- import TextShow (TextShow (.. ))
35
- import qualified TextShow as TS
36
24
import Prelude
25
+ import qualified Data.HashMap.Strict as HashMap
26
+ import qualified Data.Text as Text
37
27
38
- import Duckling.AmountOfMoney.Types (AmountOfMoneyData )
39
- import Duckling.Distance.Types (DistanceData )
40
- import Duckling.Duration.Types (DurationData )
41
- import Duckling.Email.Types (EmailData )
42
- import Duckling.Numeral.Types (NumeralData )
43
- import Duckling.Ordinal.Types (OrdinalData )
44
- import Duckling.PhoneNumber.Types (PhoneNumberData )
45
- import Duckling.Quantity.Types (QuantityData )
46
- import Duckling.Regex.Types (GroupMatch )
47
- import Duckling.Temperature.Types (TemperatureData )
48
- import Duckling.Time.Types (TimeData )
49
- import Duckling.TimeGrain.Types (Grain )
50
- import Duckling.Url.Types (UrlData )
51
- import Duckling.Volume.Types (VolumeData )
52
-
53
- -- -----------------------------------------------------------------
54
- -- Dimension
55
-
56
- -- | GADT for differentiating between dimensions
57
- -- Each dimension should have its own constructor and provide the data structure
58
- -- for its parsed data
59
- data Dimension a where
60
- RegexMatch :: Dimension GroupMatch
61
- AmountOfMoney :: Dimension AmountOfMoneyData
62
- Distance :: Dimension DistanceData
63
- Duration :: Dimension DurationData
64
- Email :: Dimension EmailData
65
- Numeral :: Dimension NumeralData
66
- Ordinal :: Dimension OrdinalData
67
- PhoneNumber :: Dimension PhoneNumberData
68
- Quantity :: Dimension QuantityData
69
- Temperature :: Dimension TemperatureData
70
- Time :: Dimension TimeData
71
- TimeGrain :: Dimension Grain
72
- Url :: Dimension UrlData
73
- Volume :: Dimension VolumeData
74
-
75
- -- Show
76
- instance Show (Dimension a ) where
77
- show RegexMatch = " RegexMatch"
78
- show Distance = " Distance"
79
- show Duration = " Duration"
80
- show Email = " Email"
81
- show AmountOfMoney = " AmountOfMoney"
82
- show Numeral = " Numeral"
83
- show Ordinal = " Ordinal"
84
- show PhoneNumber = " PhoneNumber"
85
- show Quantity = " Quantity"
86
- show Temperature = " Temperature"
87
- show Time = " Time"
88
- show TimeGrain = " TimeGrain"
89
- show Url = " Url"
90
- show Volume = " Volume"
91
- instance GShow Dimension where gshowsPrec = showsPrec
92
-
93
- -- TextShow
94
- instance TextShow (Dimension a ) where
95
- showb d = TS. fromString $ show d
96
- instance TextShow (Some Dimension ) where
97
- showb (This d) = showb d
98
-
99
- -- Hashable
100
- instance Hashable (Some Dimension ) where
101
- hashWithSalt s (This a) = hashWithSalt s a
102
- instance Hashable (Dimension a ) where
103
- hashWithSalt s RegexMatch = hashWithSalt s (0 :: Int )
104
- hashWithSalt s Distance = hashWithSalt s (1 :: Int )
105
- hashWithSalt s Duration = hashWithSalt s (2 :: Int )
106
- hashWithSalt s Email = hashWithSalt s (3 :: Int )
107
- hashWithSalt s AmountOfMoney = hashWithSalt s (4 :: Int )
108
- hashWithSalt s Numeral = hashWithSalt s (5 :: Int )
109
- hashWithSalt s Ordinal = hashWithSalt s (6 :: Int )
110
- hashWithSalt s PhoneNumber = hashWithSalt s (7 :: Int )
111
- hashWithSalt s Quantity = hashWithSalt s (8 :: Int )
112
- hashWithSalt s Temperature = hashWithSalt s (9 :: Int )
113
- hashWithSalt s Time = hashWithSalt s (10 :: Int )
114
- hashWithSalt s TimeGrain = hashWithSalt s (11 :: Int )
115
- hashWithSalt s Url = hashWithSalt s (12 :: Int )
116
- hashWithSalt s Volume = hashWithSalt s (13 :: Int )
117
-
28
+ import Duckling.Types
118
29
119
30
toName :: Dimension a -> Text
120
31
toName RegexMatch = " regex"
@@ -131,6 +42,7 @@ toName Time = "time"
131
42
toName TimeGrain = " time-grain"
132
43
toName Url = " url"
133
44
toName Volume = " volume"
45
+ toName (CustomDimension dim) = Text. pack (show dim)
134
46
135
47
fromName :: Text -> Maybe (Some Dimension )
136
48
fromName name = HashMap. lookup name m
@@ -149,33 +61,3 @@ fromName name = HashMap.lookup name m
149
61
, (" url" , This Url )
150
62
, (" volume" , This Volume )
151
63
]
152
-
153
- instance GEq Dimension where
154
- geq RegexMatch RegexMatch = Just Refl
155
- geq RegexMatch _ = Nothing
156
- geq Distance Distance = Just Refl
157
- geq Distance _ = Nothing
158
- geq Duration Duration = Just Refl
159
- geq Duration _ = Nothing
160
- geq Email Email = Just Refl
161
- geq Email _ = Nothing
162
- geq AmountOfMoney AmountOfMoney = Just Refl
163
- geq AmountOfMoney _ = Nothing
164
- geq Numeral Numeral = Just Refl
165
- geq Numeral _ = Nothing
166
- geq Ordinal Ordinal = Just Refl
167
- geq Ordinal _ = Nothing
168
- geq PhoneNumber PhoneNumber = Just Refl
169
- geq PhoneNumber _ = Nothing
170
- geq Quantity Quantity = Just Refl
171
- geq Quantity _ = Nothing
172
- geq Temperature Temperature = Just Refl
173
- geq Temperature _ = Nothing
174
- geq Time Time = Just Refl
175
- geq Time _ = Nothing
176
- geq TimeGrain TimeGrain = Just Refl
177
- geq TimeGrain _ = Nothing
178
- geq Url Url = Just Refl
179
- geq Url _ = Nothing
180
- geq Volume Volume = Just Refl
181
- geq Volume _ = Nothing
0 commit comments