2016-01-13 17:43:44 +03:00
{- # LANGUAGE FlexibleInstances # -}
2015-12-03 05:40:34 +03:00
module Range where
2015-12-15 19:48:26 +03:00
import qualified Data.Text as T
2015-12-15 00:23:09 +03:00
import Control.Applicative ( ( <|> ) )
2015-12-14 20:44:48 +03:00
import qualified Data.Char as Char
2015-12-24 01:48:43 +03:00
import Data.Maybe ( fromMaybe )
2016-02-27 03:55:14 +03:00
import Data.Option
2015-12-14 20:44:48 +03:00
2015-12-21 20:23:21 +03:00
-- | A half-open interval of integers, defined by start & end indices.
2015-12-24 01:41:35 +03:00
data Range = Range { start :: ! Int , end :: ! Int }
2015-12-03 05:40:34 +03:00
deriving ( Eq , Show )
2016-02-29 18:00:02 +03:00
-- | Make a range at a given index.
rangeAt :: Int -> Range
rangeAt a = Range a a
2016-01-13 22:38:57 +03:00
-- | Return the length of the range.
2016-01-12 19:52:38 +03:00
rangeLength :: Range -> Int
rangeLength range = end range - start range
2016-01-13 22:38:57 +03:00
-- | Return the portion of the text identified by the given range.
2015-12-15 19:48:26 +03:00
substring :: Range -> T . Text -> T . Text
2016-01-12 19:52:38 +03:00
substring range = T . take ( rangeLength range ) . T . drop ( start range )
2015-12-03 05:40:34 +03:00
2016-01-13 22:38:57 +03:00
-- | Return the portion of the list identified by the given range.
2015-12-24 05:39:35 +03:00
sublist :: Range -> [ a ] -> [ a ]
2016-01-12 19:52:38 +03:00
sublist range = take ( rangeLength range ) . drop ( start range )
2015-12-24 05:39:35 +03:00
2016-01-13 22:38:57 +03:00
-- | Return a range that covers the entire text.
2015-12-15 23:08:24 +03:00
totalRange :: T . Text -> Range
totalRange t = Range 0 $ T . length t
2015-12-04 17:20:23 +03:00
2016-01-13 22:38:57 +03:00
-- | Return a range that has its start and end offset by the given amount.
2015-12-14 20:20:51 +03:00
offsetRange :: Int -> Range -> Range
offsetRange i ( Range start end ) = Range ( i + start ) ( i + end )
2016-01-13 22:38:57 +03:00
-- | Break a string down into words and sequences of punctuation. Return a list
-- | strings with ranges, assuming that the first character in the string is
-- | at the given index.
2015-12-14 23:37:30 +03:00
rangesAndWordsFrom :: Int -> String -> [ ( Range , String ) ]
2015-12-15 00:20:42 +03:00
rangesAndWordsFrom _ " " = []
2016-01-13 20:39:52 +03:00
rangesAndWordsFrom startIndex string = fromMaybe [] $ take isWord <|> take isPunctuation <|> skip Char . isSpace
2015-12-14 20:44:48 +03:00
where
2016-01-13 21:54:49 +03:00
save parsed = ( Range startIndex $ endFor parsed , parsed )
2016-01-13 21:55:09 +03:00
take = parse ( Just . save )
skip = parse ( const Nothing )
2015-12-15 01:18:24 +03:00
endFor parsed = startIndex + length parsed
2016-01-13 22:06:59 +03:00
parse transform predicate = case span predicate string of
2015-12-15 00:07:49 +03:00
( [] , _ ) -> Nothing
2016-01-13 22:06:59 +03:00
( parsed , rest ) -> Just $ maybe id ( : ) ( transform parsed ) $ rangesAndWordsFrom ( endFor parsed ) rest
2015-12-14 23:02:09 +03:00
-- | Is this a word character?
-- | Word characters are defined as in [Ruby’ s `\p{Word}` syntax](http://ruby-doc.org/core-2.1.1/Regexp.html#class-Regexp-label-Character+Properties), i.e.:
-- | > A member of one of the following Unicode general category _Letter_, _Mark_, _Number_, _Connector_Punctuation_
2015-12-14 23:01:38 +03:00
isWord c = Char . isLetter c || Char . isNumber c || Char . isMark c || Char . generalCategory c == Char . ConnectorPunctuation
2016-01-13 20:39:52 +03:00
isPunctuation c = not ( Char . isSpace c || isWord c )
2015-12-14 23:01:38 +03:00
2015-12-21 20:22:52 +03:00
-- | Return Just the last index from a non-empty range, or if the range is empty, Nothing.
2015-12-21 20:22:20 +03:00
maybeLastIndex :: Range -> Maybe Int
maybeLastIndex ( Range start end ) | start == end = Nothing
maybeLastIndex ( Range _ end ) = Just $ end - 1
2015-12-14 20:44:48 +03:00
2016-01-13 22:38:57 +03:00
-- | Return a range that contains both the given ranges.
2016-01-13 17:49:50 +03:00
unionRange :: Range -> Range -> Range
unionRange ( Range start1 end1 ) ( Range start2 end2 ) = Range ( min start1 start2 ) ( max end1 end2 )
2016-03-03 23:58:48 +03:00
-- | Return a range that contains all the ranges in a Foldable, or Range 0 0 if it’ s empty.
2015-12-30 21:45:04 +03:00
unionRanges :: ( Functor f , Foldable f ) => f Range -> Range
2016-03-04 00:00:07 +03:00
unionRanges = unionRangesFrom ( Range 0 0 )
2016-01-13 17:43:44 +03:00
2016-03-03 23:59:40 +03:00
-- | Return a range that contains all the ranges in a Foldable, or the passed Range if the Foldable is empty.
2016-03-05 04:07:52 +03:00
unionRangesFrom :: Foldable f => Range -> f Range -> Range
unionRangesFrom range = fromMaybe range . maybeConcat
2016-03-03 23:59:40 +03:00
2016-02-27 03:55:14 +03:00
instance Monoid ( Option Range ) where
mempty = Option Nothing
mappend ( Option ( Just a ) ) ( Option ( Just b ) ) = Option ( Just ( unionRange a b ) )
mappend a @ ( Option ( Just _ ) ) _ = a
mappend _ b @ ( Option ( Just _ ) ) = b
mappend _ _ = mempty
2015-12-30 18:05:31 +03:00
2015-12-03 05:40:34 +03:00
instance Ord Range where
a <= b = start a <= start b