{-# OPTIONS -fno-warn-missing-methods #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE EmptyDataDecls #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE NoRebindableSyntax #-}
{-# LANGUAGE PackageImports #-}
{-# LANGUAGE StandaloneDeriving #-}
module Data.Text
( Text
, pack
, unpack
, fromString
, empty
, showInt
, toShortest
, putStrLn
, splitOn
, stripSuffix
, cons
, snoc
, append
, (<>)
, uncons
, head
, init
, last
, tail
, null
, length
, maximum
, all
, any
, concatMap
, concat
, minimum
, toLower
, toUpper
, map
, intercalate
, intersperse
, reverse
, isPrefixOf
, drop
, take
, unlines
, lines
) where
import Data.Data
import FFI
import Data.Nullable (fromNullable)
import Prelude (Eq,String,Int,Bool,Char,Maybe,Double,Ord,Show,error)
import qualified "base" Data.String as B (IsString (..))
data Text
deriving instance Eq Text
deriving instance Data Text
deriving instance Typeable Text
deriving instance Show Text
instance Ord Text
instance B.IsString Text where fromString :: String -> Text
fromString = String -> String -> Text
forall a. String -> a
error String
"the method fromString can never be called"
intercalate :: Text -> [Text] -> Text
intercalate :: Text -> [Text] -> Text
intercalate = String -> Text -> [Text] -> Text
forall s a. IsString s => s -> a
ffi String
"%2.join(%1)"
fromString :: String -> Text
fromString :: String -> Text
fromString = String -> String -> Text
forall s a. IsString s => s -> a
ffi String
"%1"
snoc :: Text -> Char -> Text
snoc :: Text -> Char -> Text
snoc = String -> Text -> Char -> Text
forall s a. IsString s => s -> a
ffi String
"%1 + %2"
cons :: Char -> Text -> Text
cons :: Char -> Text -> Text
cons = String -> Char -> Text -> Text
forall s a. IsString s => s -> a
ffi String
"%1 + %2"
pack :: String -> Text
pack :: String -> Text
pack = String -> String -> Text
forall s a. IsString s => s -> a
ffi String
"%1"
unpack :: Text -> String
unpack :: Text -> String
unpack = String -> Text -> String
forall s a. IsString s => s -> a
ffi String
"%1"
append :: Text -> Text -> Text
append :: Text -> Text -> Text
append = String -> Text -> Text -> Text
forall s a. IsString s => s -> a
ffi String
"%1 + %2"
(<>) :: Text -> Text -> Text
<> :: Text -> Text -> Text
(<>) = String -> Text -> Text -> Text
forall s a. IsString s => s -> a
ffi String
"%1 + %2"
length :: Text -> Int
length :: Text -> Int
length = String -> Text -> Int
forall s a. IsString s => s -> a
ffi String
"%1.length"
null :: Text -> Bool
null :: Text -> Bool
null = String -> Text -> Bool
forall s a. IsString s => s -> a
ffi String
"%1.length == 0"
take :: Int -> Text -> Text
take :: Int -> Text -> Text
take = String -> Int -> Text -> Text
forall s a. IsString s => s -> a
ffi String
"%2.substring(0,%1)"
drop :: Int -> Text -> Text
drop :: Int -> Text -> Text
drop = String -> Int -> Text -> Text
forall s a. IsString s => s -> a
ffi String
"%2.substring(%1)"
empty :: Text
empty :: Text
empty = String -> Text
forall s a. IsString s => s -> a
ffi String
"\"\""
lines :: Text -> [Text]
lines :: Text -> [Text]
lines = String -> Text -> [Text]
forall s a. IsString s => s -> a
ffi String
"%1.split('\\n')"
unlines :: [Text] -> Text
unlines :: [Text] -> Text
unlines = String -> [Text] -> Text
forall s a. IsString s => s -> a
ffi String
"%1.join('\\n')"
isPrefixOf :: Text -> Text -> Bool
isPrefixOf :: Text -> Text -> Bool
isPrefixOf = String -> Text -> Text -> Bool
forall s a. IsString s => s -> a
ffi String
"%2.lastIndexOf(%1, 0) == 0"
intersperse :: Char -> Text -> Text
intersperse :: Char -> Text -> Text
intersperse = String -> Char -> Text -> Text
forall s a. IsString s => s -> a
ffi String
"%2.split('').join(%1)"
reverse :: Text -> Text
reverse :: Text -> Text
reverse = String -> Text -> Text
forall s a. IsString s => s -> a
ffi String
"%1.split('').reverse().join('')"
stripSuffix :: Text
-> Text
-> Maybe Text
stripSuffix :: Text -> Text -> Maybe Text
stripSuffix Text
prefix Text
text =
Nullable Text -> Maybe Text
forall a. Nullable a -> Maybe a
fromNullable (Text -> Text -> Nullable Text
extract Text
prefix Text
text)
where extract :: Text -> Text -> Nullable Text
extract :: Text -> Text -> Nullable Text
extract =
String -> Text -> Text -> Nullable Text
forall s a. IsString s => s -> a
ffi String
"(function(suffix,text){ return text.substring(text.length - suffix.length) == suffix? text.substring(0,text.length - suffix.length) : null; })(%1,%2)"
splitOn :: Text -> Text -> [Text]
splitOn :: Text -> Text -> [Text]
splitOn = String -> Text -> Text -> [Text]
forall s a. IsString s => s -> a
ffi String
"%2.split(%1)"
putStrLn :: Text -> Fay ()
putStrLn :: Text -> Fay ()
putStrLn = String -> Text -> Fay ()
forall s a. IsString s => s -> a
ffi String
"console.log('%%s',%1)"
toShortest :: Double -> Text
toShortest :: Double -> Text
toShortest = String -> Double -> Text
forall s a. IsString s => s -> a
ffi String
"%1.toString()"
showInt :: Int -> Text
showInt :: Int -> Text
showInt = String -> Int -> Text
forall s a. IsString s => s -> a
ffi String
"%1.toString()"
uncons :: Text -> Maybe (Char, Text)
uncons :: Text -> Maybe (Char, Text)
uncons = String -> Text -> Maybe (Char, Text)
forall s a. IsString s => s -> a
ffi String
"%1[0] ? { instance: 'Just', slot1 : [%1[0],%1.slice(1)] } : { instance : 'Nothing' }"
head :: Text -> Char
head :: Text -> Char
head = String -> Text -> Char
forall s a. IsString s => s -> a
ffi String
"%1[0] || (function () {throw new Error('Data.Text.head: empty Text'); }())"
last :: Text -> Char
last :: Text -> Char
last = String -> Text -> Char
forall s a. IsString s => s -> a
ffi String
"%1.length ? %1[%1.length-1] : (function() { throw new Error('Data.Text.last: empty Text') })()"
tail :: Text -> Text
tail :: Text -> Text
tail = String -> Text -> Text
forall s a. IsString s => s -> a
ffi String
"%1.length ? %1.slice(1) : (function () { throw new Error('Data.Text.tail: empty Text') })()"
init :: Text -> Text
init :: Text -> Text
init = String -> Text -> Text
forall s a. IsString s => s -> a
ffi String
"%1.length ? %1.slice(0,-1) : (function () { throw new Error('Data.Text.init: empty Text') })()"
map :: (Char -> Char) -> Text -> Text
map :: (Char -> Char) -> Text -> Text
map = String -> (Char -> Char) -> Text -> Text
forall s a. IsString s => s -> a
ffi String
"[].map.call(%2, %1).join('')"
toLower :: Text -> Text
toLower :: Text -> Text
toLower = String -> Text -> Text
forall s a. IsString s => s -> a
ffi String
"%1.toLowerCase()"
toUpper :: Text -> Text
toUpper :: Text -> Text
toUpper = String -> Text -> Text
forall s a. IsString s => s -> a
ffi String
"%1.toUpperCase()"
concat :: [Text] -> Text
concat :: [Text] -> Text
concat = String -> [Text] -> Text
forall s a. IsString s => s -> a
ffi String
"%1.join('')"
concatMap :: (Char -> Text) -> Text -> Text
concatMap :: (Char -> Text) -> Text -> Text
concatMap = String -> (Char -> Text) -> Text -> Text
forall s a. IsString s => s -> a
ffi String
"[].map.call(%2, %1).join('')"
any :: (Char -> Bool) -> Text -> Bool
any :: (Char -> Bool) -> Text -> Bool
any = String -> (Char -> Bool) -> Text -> Bool
forall s a. IsString s => s -> a
ffi String
"[].filter.call(%2, %1).length > 0"
all :: (Char -> Bool) -> Text -> Bool
all :: (Char -> Bool) -> Text -> Bool
all = String -> (Char -> Bool) -> Text -> Bool
forall s a. IsString s => s -> a
ffi String
"[].filter.call(%2, %1).length == %1.length"
maximum :: Text -> Char
maximum :: Text -> Char
maximum = String -> Text -> Char
forall s a. IsString s => s -> a
ffi String
"(function (s) { \
\ if (s === '') { throw new Error('Data.Text.maximum: empty string'); } \
\ var max = s[0]; \
\ for (var i = 1; i < s.length; s++) { \
\ if (s[i] > max) { max = s[i]; } \
\ } \
\ return max; \
\ })(%1)"
minimum :: Text -> Char
minimum :: Text -> Char
minimum = String -> Text -> Char
forall s a. IsString s => s -> a
ffi String
"(function (s) { \
\ if (s === '') { throw new Error('Data.Text.maximum: empty string'); } \
\ var min = s[0]; \
\ for (var i = 1; i < s.length; s++) { \
\ if (s[i] < min) { min = s[i]; } \
\ } \
\ return min; \
\ })(%1)"