{-# 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 = s -> full
forall s full. (StringLike s, ListLike full s) => s -> full
myLines
    
    words :: ListLike full s => s -> full
    words = s -> full
forall s full. (StringLike s, ListLike full s) => s -> full
myWords
    
    unlines :: ListLike full s => full -> s
    unlines = full -> s
forall s full. (StringLike s, ListLike full s) => full -> s
myUnlines
    
    unwords :: ListLike full s => full -> s
    unwords = full -> s
forall s full. (StringLike s, ListLike full s) => full -> s
myUnwords
    
    show :: Show a => a -> s
    show = String -> s
forall a. IsString a => String -> a
fromString (String -> s) -> (a -> String) -> a -> s
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> String
forall a. Show a => a -> String
Prelude.show
    fromStringLike :: StringLike s' => s -> s'
    fromStringLike = String -> s'
forall a. IsString a => String -> a
fromString (String -> s') -> (s -> String) -> s -> s'
forall b c a. (b -> c) -> (a -> b) -> a -> c
. s -> String
forall s. StringLike s => s -> String
toString
    
    fromText :: StringLike Text => Text -> s
    fromText = String -> s
forall a. IsString a => String -> a
fromString (String -> s) -> (Text -> String) -> Text -> s
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> String
forall s. StringLike s => s -> String
toString
    
    fromLazyText :: StringLike Lazy.Text => Lazy.Text -> s
    fromLazyText = String -> s
forall a. IsString a => String -> a
fromString (String -> s) -> (Text -> String) -> Text -> s
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> String
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 = (String -> s) -> [String] -> full
forall full' item'.
ListLike full' item' =>
(String -> item') -> [String] -> full'
forall full item full' item'.
(ListLike full item, ListLike full' item') =>
(item -> item') -> full -> full'
map String -> s
forall a. IsString a => String -> a
fromString ([String] -> full) -> (s -> [String]) -> s -> full
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> [String]
L.lines (String -> [String]) -> (s -> String) -> s -> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. s -> String
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 = (String -> s) -> [String] -> full
forall full' item'.
ListLike full' item' =>
(String -> item') -> [String] -> full'
forall full item full' item'.
(ListLike full item, ListLike full' item') =>
(item -> item') -> full -> full'
map String -> s
forall a. IsString a => String -> a
fromString ([String] -> full) -> (s -> [String]) -> s -> full
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> [String]
L.words (String -> [String]) -> (s -> String) -> s -> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. s -> String
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 = String -> s
forall a. IsString a => String -> a
fromString (String -> s) -> (full -> String) -> full -> s
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [String] -> String
L.unlines ([String] -> String) -> (full -> [String]) -> full -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (s -> String) -> full -> [String]
forall full' item'.
ListLike full' item' =>
(s -> item') -> full -> full'
forall full item full' item'.
(ListLike full item, ListLike full' item') =>
(item -> item') -> full -> full'
map s -> String
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 = String -> s
forall a. IsString a => String -> a
fromString (String -> s) -> (full -> String) -> full -> s
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [String] -> String
L.unwords ([String] -> String) -> (full -> [String]) -> full -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (s -> String) -> full -> [String]
forall full' item'.
ListLike full' item' =>
(s -> item') -> full -> full'
forall full item full' item'.
(ListLike full item, ListLike full' item') =>
(item -> item') -> full -> full'
map s -> String
forall s. StringLike s => s -> String
toString