|
3 | 3 | {-# LANGUAGE UnliftedFFITypes #-}
|
4 | 4 | {-# LANGUAGE ScopedTypeVariables #-}
|
5 | 5 | {-# LANGUAGE TypeApplications #-}
|
| 6 | +{-# LANGUAGE TemplateHaskellQuotes #-} |
| 7 | +{-# LANGUAGE ViewPatterns #-} -- needed to quote a view pattern |
6 | 8 |
|
7 | 9 | module System.OsString.Internal where
|
8 | 10 |
|
@@ -122,30 +124,33 @@ fromBytes = fmap OsString . PF.fromBytes
|
122 | 124 |
|
123 | 125 | -- | QuasiQuote an 'OsString'. This accepts Unicode characters
|
124 | 126 | -- and encodes as UTF-8 on unix and UTF-16 on windows.
|
| 127 | +-- If used as pattern, requires turning on the @ViewPatterns@ extension. |
125 | 128 | osstr :: QuasiQuoter
|
126 | 129 | osstr =
|
127 | 130 | QuasiQuoter
|
128 | 131 | #if defined(mingw32_HOST_OS) || defined(__MINGW32__)
|
129 | 132 | { quoteExp = \s -> do
|
130 | 133 | osp <- either (fail . show) (pure . OsString) . PF.encodeWith (mkUTF16le ErrorOnCodingFailure) $ s
|
131 | 134 | 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)|] |
134 | 138 | , 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)" |
136 | 140 | , 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)" |
138 | 142 | }
|
139 | 143 | #else
|
140 | 144 | { quoteExp = \s -> do
|
141 | 145 | osp <- either (fail . show) (pure . OsString) . PF.encodeWith (mkUTF8 ErrorOnCodingFailure) $ s
|
142 | 146 | 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)|] |
145 | 150 | , 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)" |
147 | 152 | , 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)" |
149 | 154 | }
|
150 | 155 | #endif
|
151 | 156 |
|
|
0 commit comments