diff --git a/System/OsPath/Posix.hs b/System/OsPath/Posix.hs
index 266e9c32000d2a3693ec52259b9e17f9e29e385c..0c933b05fb15ff1c337b8ab7d9d4b3e4e37ba4d0 100644
--- a/System/OsPath/Posix.hs
+++ b/System/OsPath/Posix.hs
@@ -1,4 +1,6 @@
 {-# LANGUAGE CPP #-}
+{-# LANGUAGE TemplateHaskellQuotes #-}
+{-# LANGUAGE ViewPatterns #-}
 
 #undef  WINDOWS
 #define POSIX
@@ -18,10 +20,11 @@ pstr =
       ps <- either (fail . show) pure $ encodeWith (mkUTF8 ErrorOnCodingFailure) s
       when (not $ isValid ps) $ fail ("filepath not valid: " ++ show ps)
       lift ps
-  , quotePat  = \_ ->
-      fail "illegal QuasiQuote (allowed as expression only, used as a pattern)"
+  , quotePat = \s -> do
+      osp' <- either (fail . show) pure . encodeWith (mkUTF8 ErrorOnCodingFailure) $ s
+      [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)"
   }
diff --git a/System/OsPath/Windows.hs b/System/OsPath/Windows.hs
index 89d6faa92412066dc6d52fe3011950299b4a85ec..450f16b228ee907ab0d1b3cd158e88adfe587e2d 100644
--- a/System/OsPath/Windows.hs
+++ b/System/OsPath/Windows.hs
@@ -1,4 +1,6 @@
 {-# LANGUAGE CPP #-}
+{-# LANGUAGE TemplateHaskellQuotes #-}
+{-# LANGUAGE ViewPatterns #-}
 
 #undef  POSIX
 #define IS_WINDOWS True
@@ -19,10 +21,11 @@ pstr =
       ps <- either (fail . show) pure $ encodeWith (mkUTF16le ErrorOnCodingFailure) s
       when (not $ isValid ps) $ fail ("filepath not valid: " ++ show ps)
       lift ps
-  , quotePat  = \_ ->
-      fail "illegal QuasiQuote (allowed as expression only, used as a pattern)"
+  , quotePat = \s -> do
+      osp' <- either (fail . show) pure . encodeWith (mkUTF16le ErrorOnCodingFailure) $ s
+      [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)"
   }