[commit: packages/filepath] master: Avoid using isJust/fromJust, switch to pattern guards (acf23e1)

git at git.haskell.org git at git.haskell.org
Thu Mar 19 11:37:45 UTC 2015


Repository : ssh://git@git.haskell.org/filepath

On branch  : master
Link       : http://git.haskell.org/packages/filepath.git/commitdiff/acf23e116c039143af56896874033825cc1b7c73

>---------------------------------------------------------------

commit acf23e116c039143af56896874033825cc1b7c73
Author: Neil Mitchell <ndmitchell at gmail.com>
Date:   Fri Nov 21 16:30:25 2014 +0000

    Avoid using isJust/fromJust, switch to pattern guards


>---------------------------------------------------------------

acf23e116c039143af56896874033825cc1b7c73
 System/FilePath/Internal.hs | 16 +++++-----------
 1 file changed, 5 insertions(+), 11 deletions(-)

diff --git a/System/FilePath/Internal.hs b/System/FilePath/Internal.hs
index 3e8c952..f7b3469 100644
--- a/System/FilePath/Internal.hs
+++ b/System/FilePath/Internal.hs
@@ -1,6 +1,7 @@
 #if __GLASGOW_HASKELL__ >= 704
 {-# LANGUAGE Safe #-}
 #endif
+{-# LANGUAGE PatternGuards #-}
 
 -- This template expects CPP definitions for:
 --     MODULE_NAME = Posix | Windows
@@ -102,7 +103,7 @@ module System.FilePath.MODULE_NAME
     where
 
 import Data.Char(toLower, toUpper, isAsciiLower, isAsciiUpper)
-import Data.Maybe(isJust, fromJust)
+import Data.Maybe(isJust)
 
 import System.Environment(getEnv)
 
@@ -366,16 +367,9 @@ isLetter x = isAsciiLower x || isAsciiUpper x
 -- > Posix:   splitDrive "file" == ("","file")
 splitDrive :: FilePath -> (FilePath, FilePath)
 splitDrive x | isPosix = span (== '/') x
-
-splitDrive x | isJust y = fromJust y
-    where y = readDriveLetter x
-
-splitDrive x | isJust y = fromJust y
-    where y = readDriveUNC x
-
-splitDrive x | isJust y = fromJust y
-    where y = readDriveShare x
-
+splitDrive x | Just y <- readDriveLetter x = y
+splitDrive x | Just y <- readDriveUNC x = y
+splitDrive x | Just y <- readDriveShare x = y
 splitDrive x = ("",x)
 
 addSlash :: FilePath -> FilePath -> (FilePath, FilePath)



More information about the ghc-commits mailing list