Skip to content

Commit

Permalink
[kowainik#18] Add LazyStrict type class (kowainik#33)
Browse files Browse the repository at this point in the history
* [kowainik#18] Add LazyStrict type class

* Remove map = fmap, reexport from Data.List
  • Loading branch information
vrom911 authored and chshersh committed Jul 20, 2018
1 parent 7a9d326 commit 0e110e8
Show file tree
Hide file tree
Showing 6 changed files with 52 additions and 30 deletions.
3 changes: 3 additions & 0 deletions CHANGELOG.md
Original file line number Diff line number Diff line change
Expand Up @@ -26,6 +26,9 @@ Change log
`whenLeft_` and `whenRight_`, `whenLeftM_` and `whenRightM_`.
Add `whenLeft`, `whenRight`, `whenLeftM`, `whenRightM` which return
the value.
* [#18](https://github.com/kowainik/universum/issues/18):
Add `LazyStrict` type class for conversions.
* `map` is not `fmap` anymore. Reexport `map` from `Data.List`


`universum` uses [PVP Versioning][1].
Expand Down
1 change: 0 additions & 1 deletion README.md
Original file line number Diff line number Diff line change
Expand Up @@ -125,7 +125,6 @@ Gotchas [↑](#structure-of-this-tutorial)
* `head`, `tail`, `last`, `init` work with `NonEmpty a` instead of `[a]`.
* Safe analogue for `head` function: `safeHead :: [a] -> Maybe a`.
* `undefined` triggers a compiler warning, which is probably not what you want. Either use `throwIO`, `Except`, `error` or `bug`.
* `map` is `fmap` now.
* Multiple sorting functions are available without imports:
+ `sortBy :: (a -> a -> Ordering) -> [a] -> [a]`: sorts list using given custom comparator.
+ `sortWith :: Ord b => (a -> b) -> [a] -> [a]`: sorts a list based on some property of its elements.
Expand Down
28 changes: 8 additions & 20 deletions src/Universum/Functor/Fmap.hs
Original file line number Diff line number Diff line change
@@ -1,33 +1,21 @@
{-# LANGUAGE Safe #-}

{-
Copyright: (c) 2016 Stephen Diehl
(c) 20016-2018 Serokell
(c) 2018 Kowainik
License: MIT
-}

-- | This module contains useful functions to work with 'Functor' type class.

module Universum.Functor.Fmap
( map
, (<<$>>)
( (<<$>>)
) where

import Universum.Function ((.))
import Universum.Functor.Reexport (Functor (..))

-- $setup
-- >>> import Universum.Base (negate)
-- >>> import Universum.Bool (Bool (..), not)
-- >>> import Universum.Lifted (getLine)
-- >>> import Universum.Monad (Maybe (..))
-- >>> import Universum.String (toString)

{- | 'Prelude.map' generalized to 'Functor'.
>>> map not (Just True)
Just False
>>> map not [True,False,True,True]
[False,True,False,False]
-}
map :: Functor f => (a -> b) -> f a -> f b
map = fmap

-- $setup
-- >>> import Universum.Base (negate)
-- >>> import Universum.Monad (Maybe (..))
Expand Down
4 changes: 2 additions & 2 deletions src/Universum/List/Reexport.hs
Original file line number Diff line number Diff line change
Expand Up @@ -10,8 +10,8 @@ module Universum.List.Reexport

import Data.List (break, cycle, drop, dropWhile, filter, genericDrop, genericLength,
genericReplicate, genericSplitAt, genericTake, group, inits, intercalate,
intersperse, isPrefixOf, iterate, permutations, repeat, replicate, reverse, scanl,
scanr, sort, sortBy, sortOn, splitAt, subsequences, tails, take, takeWhile,
intersperse, isPrefixOf, iterate, map, permutations, repeat, replicate, reverse,
scanl, scanr, sort, sortBy, sortOn, splitAt, subsequences, tails, take, takeWhile,
transpose, unfoldr, unzip, unzip3, zip, zip3, zipWith, (++))
import Data.List.NonEmpty (NonEmpty (..), head, init, last, nonEmpty, tail)

Expand Down
44 changes: 39 additions & 5 deletions src/Universum/String/Conversion.hs
Original file line number Diff line number Diff line change
@@ -1,8 +1,9 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE ExplicitForAll #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE TypeSynonymInstances #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE ExplicitForAll #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE TypeSynonymInstances #-}

{-
Copyright: (c) 2016 Stephen Diehl
Expand All @@ -27,6 +28,9 @@ module Universum.String.Conversion
, ToString (..)
, ToLText (..)
, ToText (..)
, LazyStrict (..)
, fromLazy
, fromStrict

-- * Show and read functions
, readEither
Expand Down Expand Up @@ -183,3 +187,33 @@ show x = fromString (Show.show x)
{-# SPECIALIZE show :: Show.Show a => a -> ByteString #-}
{-# SPECIALIZE show :: Show.Show a => a -> LByteString #-}
{-# SPECIALIZE show :: Show.Show a => a -> String #-}


-- | Type class for lazy-strict conversions.
class LazyStrict l s | l -> s, s -> l where
toLazy :: s -> l
toStrict :: l -> s

fromLazy :: LazyStrict l s => l -> s
fromLazy = toStrict
{-# INLINE fromLazy #-}
{-# SPECIALIZE fromLazy :: LByteString -> ByteString #-}
{-# SPECIALIZE fromLazy :: LText -> Text #-}

fromStrict :: LazyStrict l s => s -> l
fromStrict = toLazy
{-# INLINE fromStrict #-}
{-# SPECIALIZE fromStrict :: ByteString -> LByteString #-}
{-# SPECIALIZE fromStrict :: Text -> LText #-}

instance LazyStrict LByteString ByteString where
toLazy = LB.fromStrict
{-# INLINE toLazy #-}
toStrict = LB.toStrict
{-# INLINE toStrict #-}

instance LazyStrict LText Text where
toLazy = LT.fromStrict
{-# INLINE toLazy #-}
toStrict = LT.toStrict
{-# INLINE toStrict #-}
2 changes: 0 additions & 2 deletions src/Universum/String/Reexport.hs
Original file line number Diff line number Diff line change
Expand Up @@ -6,7 +6,6 @@ module Universum.String.Reexport

-- * Text
, module Data.Text
, module Data.Text.Lazy
, module Data.Text.Encoding
, module Data.Text.Encoding.Error
, module Text.Read
Expand All @@ -21,5 +20,4 @@ import Data.Text (Text, lines, unlines, unwords, words)
import Data.Text.Encoding (decodeUtf8', decodeUtf8With)
import Data.Text.Encoding.Error (OnDecodeError, OnError, UnicodeException, lenientDecode,
strictDecode)
import Data.Text.Lazy (fromStrict, toStrict)
import Text.Read (Read, readMaybe, reads)

0 comments on commit 0e110e8

Please sign in to comment.