{-# LANGUAGE FlexibleContexts #-}
module Data.ListLike.String
( StringLike(..)
, fromString
)
where
import Prelude hiding (length, head, last, null, tail, map, filter, concat,
any, lookup, init, all, foldl, foldr, foldl1, foldr1,
maximum, minimum, iterate, span, break, takeWhile,
dropWhile, reverse, zip, zipWith, sequence,
sequence_, mapM, mapM_, concatMap, and, or, sum,
product, repeat, replicate, cycle, take, drop,
splitAt, elem, notElem, unzip, lines, words,
unlines, unwords)
import qualified Data.List as L
import Data.ListLike.Base
import Data.String
import Data.Text (Text)
import qualified Data.Text.Lazy as Lazy (Text)
class IsString s => StringLike s where
toString :: s -> String
lines :: (ListLike full s) => s -> full
lines = forall s full. (StringLike s, ListLike full s) => s -> full
myLines
words :: ListLike full s => s -> full
words = forall s full. (StringLike s, ListLike full s) => s -> full
myWords
unlines :: ListLike full s => full -> s
unlines = forall s full. (StringLike s, ListLike full s) => full -> s
myUnlines
unwords :: ListLike full s => full -> s
unwords = forall s full. (StringLike s, ListLike full s) => full -> s
myUnwords
show :: Show a => a -> s
show = forall a. IsString a => String -> a
fromString forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Show a => a -> String
Prelude.show
fromStringLike :: StringLike s' => s -> s'
fromStringLike = forall a. IsString a => String -> a
fromString forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall s. StringLike s => s -> String
toString
fromText :: StringLike Text => Text -> s
fromText = forall a. IsString a => String -> a
fromString forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall s. StringLike s => s -> String
toString
fromLazyText :: StringLike Lazy.Text => Lazy.Text -> s
fromLazyText = forall a. IsString a => String -> a
fromString forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall s. StringLike s => s -> String
toString
{-# DEPRECATED fromStringLike "Use fromString . toString or something more efficient using local knowledge" #-}
myLines :: (StringLike s, ListLike full s) => s -> full
myLines :: forall s full. (StringLike s, ListLike full s) => s -> full
myLines = forall full item full' item'.
(ListLike full item, ListLike full' item') =>
(item -> item') -> full -> full'
map forall a. IsString a => String -> a
fromString forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> [String]
L.lines forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall s. StringLike s => s -> String
toString
myWords :: (StringLike s, ListLike full s) => s -> full
myWords :: forall s full. (StringLike s, ListLike full s) => s -> full
myWords = forall full item full' item'.
(ListLike full item, ListLike full' item') =>
(item -> item') -> full -> full'
map forall a. IsString a => String -> a
fromString forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> [String]
L.words forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall s. StringLike s => s -> String
toString
myUnlines :: (StringLike s, ListLike full s) => full -> s
myUnlines :: forall s full. (StringLike s, ListLike full s) => full -> s
myUnlines = forall a. IsString a => String -> a
fromString forall b c a. (b -> c) -> (a -> b) -> a -> c
. [String] -> String
L.unlines forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall full item full' item'.
(ListLike full item, ListLike full' item') =>
(item -> item') -> full -> full'
map forall s. StringLike s => s -> String
toString
myUnwords :: (StringLike s, ListLike full s) => full -> s
myUnwords :: forall s full. (StringLike s, ListLike full s) => full -> s
myUnwords = forall a. IsString a => String -> a
fromString forall b c a. (b -> c) -> (a -> b) -> a -> c
. [String] -> String
L.unwords forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall full item full' item'.
(ListLike full item, ListLike full' item') =>
(item -> item') -> full -> full'
map forall s. StringLike s => s -> String
toString