Skip to content

Commit

Permalink
#11, use newer foundation features
Browse files Browse the repository at this point in the history
  • Loading branch information
ndmitchell committed Jul 5, 2017
1 parent 60eed19 commit 16a3440
Show file tree
Hide file tree
Showing 2 changed files with 4 additions and 28 deletions.
16 changes: 2 additions & 14 deletions str/Str-Foundation-Unsafe.hs
Original file line number Diff line number Diff line change
@@ -1,8 +1,7 @@
{-# LANGUAGE ViewPatterns #-}

module Str(
Str,
linesCR, stripPrefix,
linesCR, S.stripPrefix,
readFileUTF8,
S.null, S.isPrefixOf, S.drop, S.span, S.length, S.toList, S.all, S.uncons,
ugly
Expand All @@ -11,27 +10,16 @@ module Str(
import qualified Foundation as S
import qualified Foundation.String as S
import qualified Foundation.IO as S
import qualified Foundation.Conduit as C
import qualified Foundation.Conduit.Textual as C
import Data.Tuple.Extra


type Str = S.String

stripPrefix :: Str -> Str -> Maybe Str
stripPrefix (S.toBytes S.UTF8 -> pre) (S.toBytes S.UTF8 -> x) =
if pre `S.isPrefixOf` x then Just $ S.fromBytesUnsafe $ S.drop (S.length pre) x else Nothing

removeR :: Str -> Str
removeR s | Just (s, c) <- S.unsnoc s, c == '\r' = s
| otherwise = s

linesCR :: Str -> [Str]
linesCR s = map removeR $ C.runConduitPure (C.yield s C..| C.lines C..| C.sinkList)
linesCR = S.lines

ugly :: S.Integral a => Integer -> a
ugly = S.fromInteger


readFileUTF8 :: FilePath -> IO Str
readFileUTF8 = fmap S.fromBytesUnsafe . S.readFile . S.fromString
16 changes: 2 additions & 14 deletions str/Str-Foundation.hs
Original file line number Diff line number Diff line change
@@ -1,8 +1,7 @@
{-# LANGUAGE ViewPatterns #-}

module Str(
Str,
linesCR, stripPrefix,
linesCR, S.stripPrefix,
readFileUTF8,
S.null, S.isPrefixOf, S.drop, S.span, S.length, S.toList, S.all, S.uncons,
ugly
Expand All @@ -11,27 +10,16 @@ module Str(
import qualified Foundation as S
import qualified Foundation.String as S
import qualified Foundation.IO as S
import qualified Foundation.Conduit as C
import qualified Foundation.Conduit.Textual as C
import Data.Tuple.Extra


type Str = S.String

stripPrefix :: Str -> Str -> Maybe Str
stripPrefix (S.toBytes S.UTF8 -> pre) (S.toBytes S.UTF8 -> x) =
if pre `S.isPrefixOf` x then Just $ S.fromBytesUnsafe $ S.drop (S.length pre) x else Nothing

removeR :: Str -> Str
removeR s | Just (s, c) <- S.unsnoc s, c == '\r' = s
| otherwise = s

linesCR :: Str -> [Str]
linesCR s = map removeR $ C.runConduitPure (C.yield s C..| C.lines C..| C.sinkList)
linesCR = S.lines

ugly :: S.Integral a => Integer -> a
ugly = S.fromInteger


readFileUTF8 :: FilePath -> IO Str
readFileUTF8 = fmap (fst3 . S.fromBytes S.UTF8) . S.readFile . S.fromString

0 comments on commit 16a3440

Please sign in to comment.