Skip to content

Commit 3873bb4

Browse files
committed
Make osstr :: QuasiQuoter valid as a pattern
Similar to haskell/filepath#210
1 parent de9a600 commit 3873bb4

File tree

1 file changed

+13
-8
lines changed

1 file changed

+13
-8
lines changed

System/OsString/Internal.hs

Lines changed: 13 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -3,6 +3,8 @@
33
{-# LANGUAGE UnliftedFFITypes #-}
44
{-# LANGUAGE ScopedTypeVariables #-}
55
{-# LANGUAGE TypeApplications #-}
6+
{-# LANGUAGE TemplateHaskellQuotes #-}
7+
{-# LANGUAGE ViewPatterns #-} -- needed to quote a view pattern
68

79
module System.OsString.Internal where
810

@@ -122,30 +124,33 @@ fromBytes = fmap OsString . PF.fromBytes
122124

123125
-- | QuasiQuote an 'OsString'. This accepts Unicode characters
124126
-- and encodes as UTF-8 on unix and UTF-16 on windows.
127+
-- If used as pattern, requires turning on the @ViewPatterns@ extension.
125128
osstr :: QuasiQuoter
126129
osstr =
127130
QuasiQuoter
128131
#if defined(mingw32_HOST_OS) || defined(__MINGW32__)
129132
{ quoteExp = \s -> do
130133
osp <- either (fail . show) (pure . OsString) . PF.encodeWith (mkUTF16le ErrorOnCodingFailure) $ s
131134
lift osp
132-
, quotePat = \_ ->
133-
fail "illegal QuasiQuote (allowed as expression only, used as a pattern)"
135+
, quotePat = \s -> do
136+
osp' <- either (fail . show) (pure . OsString) . PF.encodeWith (mkUTF16le ErrorOnCodingFailure) $ s
137+
[p|((==) osp' -> True)|]
134138
, quoteType = \_ ->
135-
fail "illegal QuasiQuote (allowed as expression only, used as a type)"
139+
fail "illegal QuasiQuote (allowed as expression or pattern only, used as a type)"
136140
, quoteDec = \_ ->
137-
fail "illegal QuasiQuote (allowed as expression only, used as a declaration)"
141+
fail "illegal QuasiQuote (allowed as expression or pattern only, used as a declaration)"
138142
}
139143
#else
140144
{ quoteExp = \s -> do
141145
osp <- either (fail . show) (pure . OsString) . PF.encodeWith (mkUTF8 ErrorOnCodingFailure) $ s
142146
lift osp
143-
, quotePat = \_ ->
144-
fail "illegal QuasiQuote (allowed as expression only, used as a pattern)"
147+
, quotePat = \s -> do
148+
osp' <- either (fail . show) (pure . OsString) . PF.encodeWith (mkUTF8 ErrorOnCodingFailure) $ s
149+
[p|((==) osp' -> True)|]
145150
, quoteType = \_ ->
146-
fail "illegal QuasiQuote (allowed as expression only, used as a type)"
151+
fail "illegal QuasiQuote (allowed as expression or pattern only, used as a type)"
147152
, quoteDec = \_ ->
148-
fail "illegal QuasiQuote (allowed as expression only, used as a declaration)"
153+
fail "illegal QuasiQuote (allowed as expression or pattern only, used as a declaration)"
149154
}
150155
#endif
151156

0 commit comments

Comments
 (0)