Skip to content
Snippets Groups Projects
Commit 229fdb34 authored by Lawrence Bell's avatar Lawrence Bell
Browse files

make `osp :: QuasiQuoter` valid as a pattern

Resolves issue #205
parent b55465e3
No related branches found
No related tags found
No related merge requests found
{-# LANGUAGE CPP #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE UnliftedFFITypes #-}
{-# LANGUAGE TemplateHaskellQuotes #-}
{-# LANGUAGE ViewPatterns #-} -- needed to quote a view pattern
module System.OsPath.Internal where
......@@ -111,7 +113,8 @@ fromBytes = OS.fromBytes
-- | QuasiQuote an 'OsPath'. This accepts Unicode characters
-- and encodes as UTF-8 on unix and UTF-16LE on windows. Runs 'isValid'
-- on the input.
-- on the input. If used as a pattern, requires turning on the @ViewPatterns@
-- extension.
osp :: QuasiQuoter
osp = QuasiQuoter
#if defined(mingw32_HOST_OS) || defined(__MINGW32__)
......@@ -119,24 +122,28 @@ osp = QuasiQuoter
osp' <- either (fail . show) (pure . OsString) . PF.encodeWith (mkUTF16le ErrorOnCodingFailure) $ s
when (not $ isValid osp') $ fail ("filepath not valid: " ++ show osp')
lift osp'
, quotePat = \_ ->
fail "illegal QuasiQuote (allowed as expression only, used as a pattern)"
, quotePat = \s -> do
osp' <- either (fail . show) (pure . OsString) . PF.encodeWith (mkUTF16le ErrorOnCodingFailure) $ s
when (not $ isValid osp') $ fail ("filepath not valid: " ++ show osp')
[p|((==) osp' -> True)|]
, quoteType = \_ ->
fail "illegal QuasiQuote (allowed as expression only, used as a type)"
fail "illegal QuasiQuote (allowed as expression or pattern only, used as a type)"
, quoteDec = \_ ->
fail "illegal QuasiQuote (allowed as expression only, used as a declaration)"
fail "illegal QuasiQuote (allowed as expression or pattern only, used as a declaration)"
}
#else
{ quoteExp = \s -> do
osp' <- either (fail . show) (pure . OsString) . PF.encodeWith (mkUTF8 ErrorOnCodingFailure) $ s
when (not $ isValid osp') $ fail ("filepath not valid: " ++ show osp')
lift osp'
, quotePat = \_ ->
fail "illegal QuasiQuote (allowed as expression only, used as a pattern)"
, quotePat = \s -> do
osp' <- either (fail . show) (pure . OsString) . PF.encodeWith (mkUTF8 ErrorOnCodingFailure) $ s
when (not $ isValid osp') $ fail ("filepath not valid: " ++ show osp')
[p|((==) osp' -> True)|]
, quoteType = \_ ->
fail "illegal QuasiQuote (allowed as expression only, used as a type)"
fail "illegal QuasiQuote (allowed as expression or pattern only, used as a type)"
, quoteDec = \_ ->
fail "illegal QuasiQuote (allowed as expression only, used as a declaration)"
fail "illegal QuasiQuote (allowed as expression or pattern only, used as a declaration)"
}
#endif
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment