Skip to content

Commit 2c5ef6e

Browse files
jessekempfJesse Kempf
authored andcommitted
Provide a QuasiQuoter for UUID literals
1 parent d1cedd8 commit 2c5ef6e

File tree

4 files changed

+59
-12
lines changed

4 files changed

+59
-12
lines changed

uuid-types/Data/UUID/Types/Internal.hs

Lines changed: 6 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -56,6 +56,8 @@ import Data.Data
5656
import Data.Functor ((<$>))
5757
import Data.Hashable
5858
import Data.List (elemIndices)
59+
import Data.Maybe (fromMaybe)
60+
import qualified Data.String as S (IsString (..))
5961
import Foreign.Ptr (Ptr)
6062

6163
import Foreign.Storable
@@ -79,6 +81,10 @@ import System.Random
7981
-- <http://tools.ietf.org/html/rfc4122 RFC 4122>.
8082
data UUID = UUID {-# UNPACK #-} !Word64 {-# UNPACK #-} !Word64
8183
deriving (Eq, Ord, Typeable)
84+
85+
instance S.IsString UUID where
86+
fromString str = fromMaybe (error ("'" ++ str ++ "' is not a valid UUID")) $ fromString str
87+
8288
{-
8389
Prior to uuid-types-1.0.4:
8490
!Word32 !Word32 !Word32 !Word32

uuid/Data/UUID/TH.hs

Lines changed: 28 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,28 @@
1+
{-# LANGUAGE TemplateHaskell #-}
2+
3+
module Data.UUID.TH (uuid) where
4+
5+
import Data.Maybe (fromMaybe)
6+
import Data.UUID (fromString, fromWords, toWords)
7+
import Language.Haskell.TH.Quote
8+
import Language.Haskell.TH.Syntax
9+
10+
uuid :: QuasiQuoter
11+
uuid = QuasiQuoter
12+
{ quoteExp = uuidExp
13+
, quotePat = \_ -> fail "illegal UUID QuasiQuote (allowed as expression only, used as a pattern)"
14+
, quoteType = \_ -> fail "illegal UUID QuasiQuote (allowed as expression only, used as a type)"
15+
, quoteDec = \_ -> fail "illegal UUID QuasiQuote (allowed as expression only, used as a declaration)"
16+
}
17+
18+
uuidExp :: String -> Q Exp
19+
uuidExp uuidStr = do
20+
w1e <- lift w1
21+
w2e <- lift w2
22+
w3e <- lift w3
23+
w4e <- lift w4
24+
return $ AppE (AppE (AppE (AppE (VarE 'fromWords) w1e) w2e) w3e) w4e
25+
where
26+
(w1, w2, w3, w4) = toWords parsedUUID
27+
parsedUUID = fromMaybe (error errmsg) $ fromString uuidStr
28+
errmsg = "'" ++ uuidStr ++ "' is not a valid UUID"

uuid/tests/TestUUID.hs

Lines changed: 11 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,4 @@
1+
{-# LANGUAGE QuasiQuotes #-}
12
{-# LANGUAGE ViewPatterns #-}
23

34
import Control.Monad (replicateM)
@@ -8,6 +9,7 @@ import Data.List (nub, (\\))
89
import Data.Maybe
910
import Data.Word
1011
import qualified Data.UUID as U
12+
import qualified Data.UUID.TH as TH
1113
import qualified Data.UUID.V1 as U
1214
import qualified Data.UUID.V3 as U3
1315
import qualified Data.UUID.V5 as U5
@@ -65,6 +67,13 @@ test_v5 =
6567
where name = map (fromIntegral . ord) "www.widgets.com" :: [Word8]
6668
uV5 = fromJust $ U.fromString "21f7f8de-8051-5b89-8680-0195ef798b6a"
6769

70+
test_qq :: Test
71+
test_qq =
72+
testCase "Quasiquoter" $
73+
[TH.uuid|123e4567-e89b-12d3-a456-426655440000|] @?= expected
74+
75+
where
76+
expected = fromJust $ U.fromString "123e4567-e89b-12d3-a456-426655440000"
6877

6978
prop_randomsValid :: Test
7079
prop_randomsValid = testProperty "Random valid" randomsValid
@@ -101,7 +110,8 @@ main = do
101110
test_null,
102111
test_v1 v1s,
103112
test_v3,
104-
test_v5
113+
test_v5,
114+
test_qq
105115
]
106116
, [ prop_randomsValid,
107117
prop_v3NotNull,

uuid/uuid.cabal

Lines changed: 14 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -30,20 +30,22 @@ Source-Repository head
3030
Subdir: uuid
3131

3232
Library
33-
Build-Depends: base >= 4.3 && < 5
34-
, binary >= 0.4 && < 0.9
35-
, bytestring >= 0.10 && < 0.11
36-
, cryptohash-sha1 >= 0.11.100 && < 0.12
37-
, cryptohash-md5 >= 0.11.100 && < 0.12
38-
, entropy >= 0.3.7 && < 0.5
39-
, network-info == 0.2.*
40-
, random >= 1.0.1 && < 1.2
41-
, time >= 1.1 && < 1.9
42-
, text >= 1.2.3 && < 1.3
43-
, uuid-types >= 1.0.2 && < 2
33+
Build-Depends: base >= 4.3 && < 5
34+
, binary >= 0.4 && < 0.9
35+
, bytestring >= 0.10 && < 0.11
36+
, cryptohash-sha1 >= 0.11.100 && < 0.12
37+
, cryptohash-md5 >= 0.11.100 && < 0.12
38+
, entropy >= 0.3.7 && < 0.5
39+
, network-info == 0.2.*
40+
, random >= 1.0.1 && < 1.2
41+
, template-haskell >= 2.10 && < 3
42+
, time >= 1.1 && < 1.9
43+
, text >= 1.2.3 && < 1.3
44+
, uuid-types >= 1.0.2 && < 2
4445

4546
Exposed-Modules:
4647
Data.UUID
48+
Data.UUID.TH
4749
Data.UUID.Util
4850
Data.UUID.V1
4951
Data.UUID.V3
@@ -72,6 +74,7 @@ Test-Suite testuuid
7274
, base
7375
, bytestring
7476
, random
77+
, template-haskell
7578
-- deps w/o inherited constraints
7679
, QuickCheck == 2.11.*
7780
, tasty == 1.0.*

0 commit comments

Comments
 (0)