{-
    Copyright 2014-2021 Mario Blazevic

    License: BSD3 (see BSD3-LICENSE.txt file)
-}

-- | This module defines two monoid transformer data types, 'OffsetPositioned' and 'LinePositioned'. Both data types add
-- a notion of the current position to their base monoid. In case of 'OffsetPositioned', the current position is a
-- simple integer offset from the beginning of the monoid, and it can be applied to any 'StableFactorial'. The
-- base monoid of 'LinePositioned' must be a 'TextualMonoid', but for the price it will keep track of the current line
-- and column numbers as well.
--
-- Line number is zero-based, column one-based:
--
-- >> let p = pure "abcd\nefgh\nijkl\nmnop\n" :: LinePositioned String
-- >> p
-- >"abcd\nefgh\nijkl\nmnop\n"
-- >> Data.Monoid.Factorial.drop 13 p
-- >Line 2, column 4: "l\nmnop\n"

{-# LANGUAGE Haskell2010 #-}

module Data.Monoid.Instances.Positioned (
   OffsetPositioned, LinePositioned, extract, position, line, column
   )
where

import Control.Applicative -- (Applicative(..))
import qualified Data.List as List
import Data.String (IsString(..))

import Data.Semigroup (Semigroup(..))
import Data.Monoid (Monoid(..), Endo(..))
import Data.Semigroup.Cancellative (LeftReductive(..), RightReductive(..))
import Data.Semigroup.Factorial (Factorial(..), StableFactorial)
import Data.Monoid.GCD (LeftGCDMonoid(..), RightGCDMonoid(..))
import Data.Monoid.Null (MonoidNull(null), PositiveMonoid)
import Data.Monoid.Factorial (FactorialMonoid(..))
import Data.Monoid.Textual (TextualMonoid(..))
import qualified Data.Semigroup.Factorial as Factorial
import qualified Data.Monoid.Factorial as Factorial
import qualified Data.Monoid.Textual as Textual

import Prelude hiding (all, any, break, filter, foldl, foldl1, foldr, foldr1, lines, map, concatMap,
                       length, null, reverse, scanl, scanr, scanl1, scanr1, span, splitAt)

class Positioned p where
   extract :: p a -> a
   position :: p a -> Int

data OffsetPositioned m = OffsetPositioned{OffsetPositioned m -> Int
offset :: !Int,
                                           -- ^ the current offset
                                           OffsetPositioned m -> m
extractOffset :: m}

data LinePositioned m = LinePositioned{LinePositioned m -> Int
fullOffset :: !Int,
                                       -- | the current line
                                       LinePositioned m -> Int
line :: !Int,
                                       LinePositioned m -> Int
lineStart :: !Int,
                                       LinePositioned m -> m
extractLines :: m}

-- | the current column
column :: LinePositioned m -> Int
column :: LinePositioned m -> Int
column LinePositioned m
lp = LinePositioned m -> Int
forall (p :: * -> *) a. Positioned p => p a -> Int
position LinePositioned m
lp Int -> Int -> Int
forall a. Num a => a -> a -> a
- LinePositioned m -> Int
forall m. LinePositioned m -> Int
lineStart LinePositioned m
lp

instance Functor OffsetPositioned where
   fmap :: (a -> b) -> OffsetPositioned a -> OffsetPositioned b
fmap a -> b
f (OffsetPositioned Int
p a
c) = Int -> b -> OffsetPositioned b
forall m. Int -> m -> OffsetPositioned m
OffsetPositioned Int
p (a -> b
f a
c)

instance Functor LinePositioned where
   fmap :: (a -> b) -> LinePositioned a -> LinePositioned b
fmap a -> b
f (LinePositioned Int
p Int
l Int
lp a
c) = Int -> Int -> Int -> b -> LinePositioned b
forall m. Int -> Int -> Int -> m -> LinePositioned m
LinePositioned Int
p Int
l Int
lp (a -> b
f a
c)

instance Applicative OffsetPositioned where
   pure :: a -> OffsetPositioned a
pure = Int -> a -> OffsetPositioned a
forall m. Int -> m -> OffsetPositioned m
OffsetPositioned Int
0
   OffsetPositioned Int
_ a -> b
f <*> :: OffsetPositioned (a -> b)
-> OffsetPositioned a -> OffsetPositioned b
<*> OffsetPositioned Int
p a
c = Int -> b -> OffsetPositioned b
forall m. Int -> m -> OffsetPositioned m
OffsetPositioned Int
p (a -> b
f a
c)

instance Applicative LinePositioned where
   pure :: a -> LinePositioned a
pure = Int -> Int -> Int -> a -> LinePositioned a
forall m. Int -> Int -> Int -> m -> LinePositioned m
LinePositioned Int
0 Int
0 (-Int
1)
   LinePositioned Int
_ Int
_ Int
_ a -> b
f <*> :: LinePositioned (a -> b) -> LinePositioned a -> LinePositioned b
<*> LinePositioned Int
p Int
l Int
lp a
c = Int -> Int -> Int -> b -> LinePositioned b
forall m. Int -> Int -> Int -> m -> LinePositioned m
LinePositioned Int
p Int
l Int
lp (a -> b
f a
c)

instance Positioned OffsetPositioned where
   extract :: OffsetPositioned a -> a
extract = OffsetPositioned a -> a
forall a. OffsetPositioned a -> a
extractOffset
   position :: OffsetPositioned a -> Int
position = OffsetPositioned a -> Int
forall a. OffsetPositioned a -> Int
offset

instance Positioned LinePositioned where
   extract :: LinePositioned a -> a
extract = LinePositioned a -> a
forall a. LinePositioned a -> a
extractLines
   position :: LinePositioned a -> Int
position = LinePositioned a -> Int
forall m. LinePositioned m -> Int
fullOffset

instance Eq m => Eq (OffsetPositioned m) where
   OffsetPositioned{extractOffset :: forall a. OffsetPositioned a -> a
extractOffset= m
a} == :: OffsetPositioned m -> OffsetPositioned m -> Bool
== OffsetPositioned{extractOffset :: forall a. OffsetPositioned a -> a
extractOffset= m
b} = m
a m -> m -> Bool
forall a. Eq a => a -> a -> Bool
== m
b

instance Eq m => Eq (LinePositioned m) where
   LinePositioned{extractLines :: forall a. LinePositioned a -> a
extractLines= m
a} == :: LinePositioned m -> LinePositioned m -> Bool
== LinePositioned{extractLines :: forall a. LinePositioned a -> a
extractLines= m
b} = m
a m -> m -> Bool
forall a. Eq a => a -> a -> Bool
== m
b

instance Ord m => Ord (OffsetPositioned m) where
   compare :: OffsetPositioned m -> OffsetPositioned m -> Ordering
compare OffsetPositioned{extractOffset :: forall a. OffsetPositioned a -> a
extractOffset= m
a} OffsetPositioned{extractOffset :: forall a. OffsetPositioned a -> a
extractOffset= m
b} = m -> m -> Ordering
forall a. Ord a => a -> a -> Ordering
compare m
a m
b

instance Ord m => Ord (LinePositioned m) where
   compare :: LinePositioned m -> LinePositioned m -> Ordering
compare LinePositioned{extractLines :: forall a. LinePositioned a -> a
extractLines= m
a} LinePositioned{extractLines :: forall a. LinePositioned a -> a
extractLines= m
b} = m -> m -> Ordering
forall a. Ord a => a -> a -> Ordering
compare m
a m
b

instance Show m => Show (OffsetPositioned m) where
   showsPrec :: Int -> OffsetPositioned m -> ShowS
showsPrec Int
prec (OffsetPositioned Int
0 m
c) = Int -> m -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
prec m
c
   showsPrec Int
prec (OffsetPositioned Int
pos m
c) = Int -> ShowS
forall a. Show a => a -> ShowS
shows Int
pos ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String
": " String -> ShowS
forall a. [a] -> [a] -> [a]
++) ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> m -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
prec m
c

instance Show m => Show (LinePositioned m) where
   showsPrec :: Int -> LinePositioned m -> ShowS
showsPrec Int
prec (LinePositioned Int
0 Int
0 (-1) m
c) = Int -> m -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
prec m
c
   showsPrec Int
prec (LinePositioned Int
pos Int
l Int
lpos m
c) =
      (String
"Line " String -> ShowS
forall a. [a] -> [a] -> [a]
++) ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> ShowS
forall a. Show a => a -> ShowS
shows Int
l ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String
", column " String -> ShowS
forall a. [a] -> [a] -> [a]
++) ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> ShowS
forall a. Show a => a -> ShowS
shows (Int
pos Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
lpos) ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String
": " String -> ShowS
forall a. [a] -> [a] -> [a]
++) ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> m -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
prec m
c

instance StableFactorial m => Semigroup (OffsetPositioned m) where
   OffsetPositioned Int
p1 m
c1 <> :: OffsetPositioned m -> OffsetPositioned m -> OffsetPositioned m
<> OffsetPositioned Int
p2 m
c2 =
      Int -> m -> OffsetPositioned m
forall m. Int -> m -> OffsetPositioned m
OffsetPositioned (if Int
p1 Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
/= Int
0 Bool -> Bool -> Bool
|| Int
p2 Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0 then Int
p1 else Int -> Int -> Int
forall a. Ord a => a -> a -> a
max Int
0 (Int -> Int) -> Int -> Int
forall a b. (a -> b) -> a -> b
$ Int
p2 Int -> Int -> Int
forall a. Num a => a -> a -> a
- m -> Int
forall m. Factorial m => m -> Int
length m
c1) (m
c1 m -> m -> m
forall a. Semigroup a => a -> a -> a
<> m
c2)
   {-# INLINE (<>) #-}

instance (FactorialMonoid m, StableFactorial m) => Monoid (OffsetPositioned m) where
   mempty :: OffsetPositioned m
mempty = m -> OffsetPositioned m
forall (f :: * -> *) a. Applicative f => a -> f a
pure m
forall a. Monoid a => a
mempty
   mappend :: OffsetPositioned m -> OffsetPositioned m -> OffsetPositioned m
mappend = OffsetPositioned m -> OffsetPositioned m -> OffsetPositioned m
forall a. Semigroup a => a -> a -> a
(<>)
   {-# INLINE mempty #-}
   {-# INLINE mappend #-}

instance (StableFactorial m, TextualMonoid m) => Semigroup (LinePositioned m) where
   LinePositioned Int
p1 Int
l1 Int
lp1 m
c1 <> :: LinePositioned m -> LinePositioned m -> LinePositioned m
<> LinePositioned Int
p2 Int
l2 Int
lp2 m
c2
     | Int
p1 Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
/= Int
0 Bool -> Bool -> Bool
|| Int
p2 Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0 = Int -> Int -> Int -> m -> LinePositioned m
forall m. Int -> Int -> Int -> m -> LinePositioned m
LinePositioned Int
p1 Int
l1 Int
lp1 m
c
     | Bool
otherwise = Int -> Int -> Int -> m -> LinePositioned m
forall m. Int -> Int -> Int -> m -> LinePositioned m
LinePositioned Int
p2' Int
l2' Int
lp2' m
c
     where c :: m
c = m -> m -> m
forall a. Monoid a => a -> a -> a
mappend m
c1 m
c2
           p2' :: Int
p2' = Int -> Int -> Int
forall a. Ord a => a -> a -> a
max Int
0 (Int -> Int) -> Int -> Int
forall a b. (a -> b) -> a -> b
$ Int
p2 Int -> Int -> Int
forall a. Num a => a -> a -> a
- m -> Int
forall m. Factorial m => m -> Int
length m
c1
           lp2' :: Int
lp2' = Int
p2' Int -> Int -> Int
forall a. Num a => a -> a -> a
- (Int
p2 Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
lp2 Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
cd Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1)
           l2' :: Int
l2' = if Int
l2 Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0 then Int
0 else Int -> Int -> Int
forall a. Ord a => a -> a -> a
max Int
0 (Int
l2 Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
ld)
           (Int
ld, Int
cd) = m -> (Int, Int)
forall m. TextualMonoid m => m -> (Int, Int)
linesColumns' m
c1
   {-# INLINE (<>) #-}

instance (StableFactorial m, TextualMonoid m) => Monoid (LinePositioned m) where
   mempty :: LinePositioned m
mempty = m -> LinePositioned m
forall (f :: * -> *) a. Applicative f => a -> f a
pure m
forall a. Monoid a => a
mempty
   mappend :: LinePositioned m -> LinePositioned m -> LinePositioned m
mappend = LinePositioned m -> LinePositioned m -> LinePositioned m
forall a. Semigroup a => a -> a -> a
(<>)
   {-# INLINE mempty #-}

instance (StableFactorial m, FactorialMonoid m) => MonoidNull (OffsetPositioned m) where
   null :: OffsetPositioned m -> Bool
null = m -> Bool
forall m. MonoidNull m => m -> Bool
null (m -> Bool)
-> (OffsetPositioned m -> m) -> OffsetPositioned m -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. OffsetPositioned m -> m
forall a. OffsetPositioned a -> a
extractOffset
   {-# INLINE null #-}

instance (StableFactorial m, TextualMonoid m, MonoidNull m) => MonoidNull (LinePositioned m) where
   null :: LinePositioned m -> Bool
null = m -> Bool
forall m. MonoidNull m => m -> Bool
null (m -> Bool) -> (LinePositioned m -> m) -> LinePositioned m -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. LinePositioned m -> m
forall a. LinePositioned a -> a
extractLines
   {-# INLINE null #-}

instance (StableFactorial m, FactorialMonoid m) => PositiveMonoid (OffsetPositioned m)

instance (StableFactorial m, TextualMonoid m) => PositiveMonoid (LinePositioned m)

instance (StableFactorial m, LeftReductive m) => LeftReductive (OffsetPositioned m) where
   isPrefixOf :: OffsetPositioned m -> OffsetPositioned m -> Bool
isPrefixOf (OffsetPositioned Int
_ m
c1) (OffsetPositioned Int
_ m
c2) = m -> m -> Bool
forall m. LeftReductive m => m -> m -> Bool
isPrefixOf m
c1 m
c2
   stripPrefix :: OffsetPositioned m
-> OffsetPositioned m -> Maybe (OffsetPositioned m)
stripPrefix (OffsetPositioned Int
_ m
c1) (OffsetPositioned Int
p m
c2) = (m -> OffsetPositioned m) -> Maybe m -> Maybe (OffsetPositioned m)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Int -> m -> OffsetPositioned m
forall m. Int -> m -> OffsetPositioned m
OffsetPositioned (Int
p Int -> Int -> Int
forall a. Num a => a -> a -> a
+ m -> Int
forall m. Factorial m => m -> Int
length m
c1)) (m -> m -> Maybe m
forall m. LeftReductive m => m -> m -> Maybe m
stripPrefix m
c1 m
c2)
   {-# INLINE isPrefixOf #-}
   {-# INLINE stripPrefix #-}

instance (StableFactorial m, TextualMonoid m) => LeftReductive (LinePositioned m) where
   isPrefixOf :: LinePositioned m -> LinePositioned m -> Bool
isPrefixOf LinePositioned m
a LinePositioned m
b = m -> m -> Bool
forall m. LeftReductive m => m -> m -> Bool
isPrefixOf (LinePositioned m -> m
forall a. LinePositioned a -> a
extractLines LinePositioned m
a) (LinePositioned m -> m
forall a. LinePositioned a -> a
extractLines LinePositioned m
b)
   stripPrefix :: LinePositioned m -> LinePositioned m -> Maybe (LinePositioned m)
stripPrefix LinePositioned{extractLines :: forall a. LinePositioned a -> a
extractLines= m
c1} (LinePositioned Int
p Int
l Int
lpos m
c2) =
      let (Int
lines, Int
columns) = m -> (Int, Int)
forall m. TextualMonoid m => m -> (Int, Int)
linesColumns' m
c1
          len :: Int
len = m -> Int
forall m. Factorial m => m -> Int
length m
c1
      in (m -> LinePositioned m) -> Maybe m -> Maybe (LinePositioned m)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Int -> Int -> Int -> m -> LinePositioned m
forall m. Int -> Int -> Int -> m -> LinePositioned m
LinePositioned (Int
p Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
len) (Int
l Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
lines) (Int
lpos Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
len Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
columns)) (m -> m -> Maybe m
forall m. LeftReductive m => m -> m -> Maybe m
stripPrefix m
c1 m
c2)
   {-# INLINE isPrefixOf #-}
   {-# INLINE stripPrefix #-}

instance (StableFactorial m, FactorialMonoid m, LeftGCDMonoid m) => LeftGCDMonoid (OffsetPositioned m) where
   commonPrefix :: OffsetPositioned m -> OffsetPositioned m -> OffsetPositioned m
commonPrefix (OffsetPositioned Int
p1 m
c1) (OffsetPositioned Int
p2 m
c2) = Int -> m -> OffsetPositioned m
forall m. Int -> m -> OffsetPositioned m
OffsetPositioned (Int -> Int -> Int
forall a. Ord a => a -> a -> a
min Int
p1 Int
p2) (m -> m -> m
forall m. LeftGCDMonoid m => m -> m -> m
commonPrefix m
c1 m
c2)
   stripCommonPrefix :: OffsetPositioned m
-> OffsetPositioned m
-> (OffsetPositioned m, OffsetPositioned m, OffsetPositioned m)
stripCommonPrefix (OffsetPositioned Int
p1 m
c1) (OffsetPositioned Int
p2 m
c2) =
      (Int -> m -> OffsetPositioned m
forall m. Int -> m -> OffsetPositioned m
OffsetPositioned (Int -> Int -> Int
forall a. Ord a => a -> a -> a
min Int
p1 Int
p2) m
prefix, Int -> m -> OffsetPositioned m
forall m. Int -> m -> OffsetPositioned m
OffsetPositioned (Int
p1 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
l) m
c1', Int -> m -> OffsetPositioned m
forall m. Int -> m -> OffsetPositioned m
OffsetPositioned (Int
p2 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
l) m
c2')
      where (m
prefix, m
c1', m
c2') = m -> m -> (m, m, m)
forall m. LeftGCDMonoid m => m -> m -> (m, m, m)
stripCommonPrefix m
c1 m
c2
            l :: Int
l = m -> Int
forall m. Factorial m => m -> Int
length m
prefix
   {-# INLINE commonPrefix #-}
   {-# INLINE stripCommonPrefix #-}

instance (StableFactorial m, TextualMonoid m, LeftGCDMonoid m) => LeftGCDMonoid (LinePositioned m) where
   commonPrefix :: LinePositioned m -> LinePositioned m -> LinePositioned m
commonPrefix (LinePositioned Int
p1 Int
l1 Int
lp1 m
c1) (LinePositioned Int
p2 Int
l2 Int
lp2 m
c2) =
      if Int
p1 Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
p2
      then Int -> Int -> Int -> m -> LinePositioned m
forall m. Int -> Int -> Int -> m -> LinePositioned m
LinePositioned Int
p1 Int
l1 Int
lp1 (m -> m -> m
forall m. LeftGCDMonoid m => m -> m -> m
commonPrefix m
c1 m
c2)
      else Int -> Int -> Int -> m -> LinePositioned m
forall m. Int -> Int -> Int -> m -> LinePositioned m
LinePositioned Int
p2 Int
l2 Int
lp2 (m -> m -> m
forall m. LeftGCDMonoid m => m -> m -> m
commonPrefix m
c1 m
c2)
   stripCommonPrefix :: LinePositioned m
-> LinePositioned m
-> (LinePositioned m, LinePositioned m, LinePositioned m)
stripCommonPrefix (LinePositioned Int
p1 Int
l1 Int
lp1 m
c1) (LinePositioned Int
p2 Int
l2 Int
lp2 m
c2) =
      let (m
prefix, m
c1', m
c2') = m -> m -> (m, m, m)
forall m. LeftGCDMonoid m => m -> m -> (m, m, m)
stripCommonPrefix m
c1 m
c2
          (Int
lines, Int
columns) = m -> (Int, Int)
forall m. TextualMonoid m => m -> (Int, Int)
linesColumns' m
prefix
          len :: Int
len = m -> Int
forall m. Factorial m => m -> Int
length m
prefix
      in (if Int
p1 Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
p2 then Int -> Int -> Int -> m -> LinePositioned m
forall m. Int -> Int -> Int -> m -> LinePositioned m
LinePositioned Int
p1 Int
l1 Int
lp1 m
prefix else Int -> Int -> Int -> m -> LinePositioned m
forall m. Int -> Int -> Int -> m -> LinePositioned m
LinePositioned Int
p2 Int
l2 Int
lp2 m
prefix,
          Int -> Int -> Int -> m -> LinePositioned m
forall m. Int -> Int -> Int -> m -> LinePositioned m
LinePositioned (Int
p1 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
len) (Int
l1 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
lines) (Int
lp1 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
len Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
columns) m
c1',
          Int -> Int -> Int -> m -> LinePositioned m
forall m. Int -> Int -> Int -> m -> LinePositioned m
LinePositioned (Int
p2 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
len) (Int
l2 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
lines) (Int
lp2 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
len Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
columns) m
c2')
   {-# INLINE commonPrefix #-}
   {-# INLINE stripCommonPrefix #-}

instance (StableFactorial m, FactorialMonoid m, RightReductive m) => RightReductive (OffsetPositioned m) where
   isSuffixOf :: OffsetPositioned m -> OffsetPositioned m -> Bool
isSuffixOf (OffsetPositioned Int
_ m
c1) (OffsetPositioned Int
_ m
c2) = m -> m -> Bool
forall m. RightReductive m => m -> m -> Bool
isSuffixOf m
c1 m
c2
   stripSuffix :: OffsetPositioned m
-> OffsetPositioned m -> Maybe (OffsetPositioned m)
stripSuffix (OffsetPositioned Int
_ m
c1) (OffsetPositioned Int
p m
c2) = (m -> OffsetPositioned m) -> Maybe m -> Maybe (OffsetPositioned m)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Int -> m -> OffsetPositioned m
forall m. Int -> m -> OffsetPositioned m
OffsetPositioned Int
p) (m -> m -> Maybe m
forall m. RightReductive m => m -> m -> Maybe m
stripSuffix m
c1 m
c2)
   {-# INLINE isSuffixOf #-}
   {-# INLINE stripSuffix #-}

instance (StableFactorial m, TextualMonoid m, RightReductive m) => RightReductive (LinePositioned m) where
   isSuffixOf :: LinePositioned m -> LinePositioned m -> Bool
isSuffixOf LinePositioned{extractLines :: forall a. LinePositioned a -> a
extractLines=m
c1} LinePositioned{extractLines :: forall a. LinePositioned a -> a
extractLines=m
c2} = m -> m -> Bool
forall m. RightReductive m => m -> m -> Bool
isSuffixOf m
c1 m
c2
   stripSuffix :: LinePositioned m -> LinePositioned m -> Maybe (LinePositioned m)
stripSuffix (LinePositioned Int
p Int
l Int
lp m
c1) LinePositioned{extractLines :: forall a. LinePositioned a -> a
extractLines=m
c2} =
      (m -> LinePositioned m) -> Maybe m -> Maybe (LinePositioned m)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Int -> Int -> Int -> m -> LinePositioned m
forall m. Int -> Int -> Int -> m -> LinePositioned m
LinePositioned Int
p Int
l Int
lp) (m -> m -> Maybe m
forall m. RightReductive m => m -> m -> Maybe m
stripSuffix m
c1 m
c2)
   {-# INLINE isSuffixOf #-}
   {-# INLINE stripSuffix #-}

instance (StableFactorial m, FactorialMonoid m, RightGCDMonoid m) => RightGCDMonoid (OffsetPositioned m) where
   commonSuffix :: OffsetPositioned m -> OffsetPositioned m -> OffsetPositioned m
commonSuffix (OffsetPositioned Int
p1 m
c1) (OffsetPositioned Int
p2 m
c2) =
      Int -> m -> OffsetPositioned m
forall m. Int -> m -> OffsetPositioned m
OffsetPositioned (Int -> Int -> Int
forall a. Ord a => a -> a -> a
min (Int
p1 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ m -> Int
forall m. Factorial m => m -> Int
length m
c1) (Int
p2 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ m -> Int
forall m. Factorial m => m -> Int
length m
c2) Int -> Int -> Int
forall a. Num a => a -> a -> a
- m -> Int
forall m. Factorial m => m -> Int
length m
suffix) m
suffix
      where suffix :: m
suffix = m -> m -> m
forall m. RightGCDMonoid m => m -> m -> m
commonSuffix m
c1 m
c2
   stripCommonSuffix :: OffsetPositioned m
-> OffsetPositioned m
-> (OffsetPositioned m, OffsetPositioned m, OffsetPositioned m)
stripCommonSuffix (OffsetPositioned Int
p1 m
c1) (OffsetPositioned Int
p2 m
c2) =
      (Int -> m -> OffsetPositioned m
forall m. Int -> m -> OffsetPositioned m
OffsetPositioned Int
p1 m
c1', Int -> m -> OffsetPositioned m
forall m. Int -> m -> OffsetPositioned m
OffsetPositioned Int
p2 m
c2',
       Int -> m -> OffsetPositioned m
forall m. Int -> m -> OffsetPositioned m
OffsetPositioned (Int -> Int -> Int
forall a. Ord a => a -> a -> a
min (Int
p1 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ m -> Int
forall m. Factorial m => m -> Int
length m
c1') (Int
p2 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ m -> Int
forall m. Factorial m => m -> Int
length m
c2')) m
suffix)
      where (m
c1', m
c2', m
suffix) = m -> m -> (m, m, m)
forall m. RightGCDMonoid m => m -> m -> (m, m, m)
stripCommonSuffix m
c1 m
c2
   {-# INLINE commonSuffix #-}
   {-# INLINE stripCommonSuffix #-}

instance (StableFactorial m, TextualMonoid m, RightGCDMonoid m) => RightGCDMonoid (LinePositioned m) where
   stripCommonSuffix :: LinePositioned m
-> LinePositioned m
-> (LinePositioned m, LinePositioned m, LinePositioned m)
stripCommonSuffix (LinePositioned Int
p1 Int
l1 Int
lp1 m
c1) (LinePositioned Int
p2 Int
l2 Int
lp2 m
c2) =
      (Int -> Int -> Int -> m -> LinePositioned m
forall m. Int -> Int -> Int -> m -> LinePositioned m
LinePositioned Int
p1 Int
l1 Int
lp1 m
c1', Int -> Int -> Int -> m -> LinePositioned m
forall m. Int -> Int -> Int -> m -> LinePositioned m
LinePositioned Int
p2 Int
l2 Int
lp2 m
c2',
       if Int
p1 Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
p2
       then Int -> Int -> Int -> m -> LinePositioned m
forall m. Int -> Int -> Int -> m -> LinePositioned m
LinePositioned (Int
p1 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
len1) (Int
l1 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
lines1) (Int
lp1 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
len1 Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
columns1) m
suffix
       else Int -> Int -> Int -> m -> LinePositioned m
forall m. Int -> Int -> Int -> m -> LinePositioned m
LinePositioned (Int
p2 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
len2) (Int
l2 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
lines2) (Int
lp2 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
len2 Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
columns2) m
suffix)
      where (m
c1', m
c2', m
suffix) = m -> m -> (m, m, m)
forall m. RightGCDMonoid m => m -> m -> (m, m, m)
stripCommonSuffix m
c1 m
c2
            len1 :: Int
len1 = m -> Int
forall m. Factorial m => m -> Int
length m
c1'
            len2 :: Int
len2 = m -> Int
forall m. Factorial m => m -> Int
length m
c2'
            (Int
lines1, Int
columns1) = m -> (Int, Int)
forall m. TextualMonoid m => m -> (Int, Int)
linesColumns' m
c1'
            (Int
lines2, Int
columns2) = m -> (Int, Int)
forall m. TextualMonoid m => m -> (Int, Int)
linesColumns' m
c2'

instance StableFactorial m => Factorial (OffsetPositioned m) where
   factors :: OffsetPositioned m -> [OffsetPositioned m]
factors (OffsetPositioned Int
p m
c) = (Int, [OffsetPositioned m]) -> [OffsetPositioned m]
forall a b. (a, b) -> b
snd ((Int, [OffsetPositioned m]) -> [OffsetPositioned m])
-> (Int, [OffsetPositioned m]) -> [OffsetPositioned m]
forall a b. (a -> b) -> a -> b
$ (Int -> m -> (Int, OffsetPositioned m))
-> Int -> [m] -> (Int, [OffsetPositioned m])
forall (t :: * -> *) a b c.
Traversable t =>
(a -> b -> (a, c)) -> a -> t b -> (a, t c)
List.mapAccumL Int -> m -> (Int, OffsetPositioned m)
forall m. Int -> m -> (Int, OffsetPositioned m)
next Int
p (m -> [m]
forall m. Factorial m => m -> [m]
factors m
c)
      where next :: Int -> m -> (Int, OffsetPositioned m)
next Int
p1 m
c1 = (Int -> Int
forall a. Enum a => a -> a
succ Int
p1, Int -> m -> OffsetPositioned m
forall m. Int -> m -> OffsetPositioned m
OffsetPositioned Int
p1 m
c1)
   primePrefix :: OffsetPositioned m -> OffsetPositioned m
primePrefix (OffsetPositioned Int
p m
c) = Int -> m -> OffsetPositioned m
forall m. Int -> m -> OffsetPositioned m
OffsetPositioned Int
p (m -> m
forall m. Factorial m => m -> m
primePrefix m
c)
   foldl :: (a -> OffsetPositioned m -> a) -> a -> OffsetPositioned m -> a
foldl a -> OffsetPositioned m -> a
f a
a0 (OffsetPositioned Int
p0 m
c0) = (a, Int) -> a
forall a b. (a, b) -> a
fst ((a, Int) -> a) -> (a, Int) -> a
forall a b. (a -> b) -> a -> b
$ ((a, Int) -> m -> (a, Int)) -> (a, Int) -> m -> (a, Int)
forall m a. Factorial m => (a -> m -> a) -> a -> m -> a
Factorial.foldl (a, Int) -> m -> (a, Int)
f' (a
a0, Int
p0) m
c0
      where f' :: (a, Int) -> m -> (a, Int)
f' (a
a, Int
p) m
c = (a -> OffsetPositioned m -> a
f a
a (Int -> m -> OffsetPositioned m
forall m. Int -> m -> OffsetPositioned m
OffsetPositioned Int
p m
c), Int -> Int
forall a. Enum a => a -> a
succ Int
p)
   foldl' :: (a -> OffsetPositioned m -> a) -> a -> OffsetPositioned m -> a
foldl' a -> OffsetPositioned m -> a
f a
a0 (OffsetPositioned Int
p0 m
c0) = (a, Int) -> a
forall a b. (a, b) -> a
fst ((a, Int) -> a) -> (a, Int) -> a
forall a b. (a -> b) -> a -> b
$ ((a, Int) -> m -> (a, Int)) -> (a, Int) -> m -> (a, Int)
forall m a. Factorial m => (a -> m -> a) -> a -> m -> a
Factorial.foldl' (a, Int) -> m -> (a, Int)
f' (a
a0, Int
p0) m
c0
      where f' :: (a, Int) -> m -> (a, Int)
f' (a
a, Int
p) m
c = let a' :: a
a' = a -> OffsetPositioned m -> a
f a
a (Int -> m -> OffsetPositioned m
forall m. Int -> m -> OffsetPositioned m
OffsetPositioned Int
p m
c) in a -> (a, Int) -> (a, Int)
seq a
a' (a
a', Int -> Int
forall a. Enum a => a -> a
succ Int
p)
   foldr :: (OffsetPositioned m -> a -> a) -> a -> OffsetPositioned m -> a
foldr OffsetPositioned m -> a -> a
f a
a0 (OffsetPositioned Int
p0 m
c0) = (m -> (Int -> a) -> Int -> a) -> (Int -> a) -> m -> Int -> a
forall m a. Factorial m => (m -> a -> a) -> a -> m -> a
Factorial.foldr m -> (Int -> a) -> Int -> a
f' (a -> Int -> a
forall a b. a -> b -> a
const a
a0) m
c0 Int
p0
      where f' :: m -> (Int -> a) -> Int -> a
f' m
c Int -> a
cont Int
p = OffsetPositioned m -> a -> a
f (Int -> m -> OffsetPositioned m
forall m. Int -> m -> OffsetPositioned m
OffsetPositioned Int
p m
c) (Int -> a
cont (Int -> a) -> Int -> a
forall a b. (a -> b) -> a -> b
$! Int -> Int
forall a. Enum a => a -> a
succ Int
p)
   foldMap :: (OffsetPositioned m -> n) -> OffsetPositioned m -> n
foldMap OffsetPositioned m -> n
f (OffsetPositioned Int
p m
c) = Endo (Int -> n) -> (Int -> n) -> Int -> n
forall a. Endo a -> a -> a
appEndo ((m -> Endo (Int -> n)) -> m -> Endo (Int -> n)
forall m n. (Factorial m, Monoid n) => (m -> n) -> m -> n
Factorial.foldMap m -> Endo (Int -> n)
f' m
c) (n -> Int -> n
forall a b. a -> b -> a
const n
forall a. Monoid a => a
mempty) Int
p
      where -- f' :: m -> Endo (Int -> m)
            f' :: m -> Endo (Int -> n)
f' m
prime = ((Int -> n) -> Int -> n) -> Endo (Int -> n)
forall a. (a -> a) -> Endo a
Endo (\Int -> n
cont Int
pos-> OffsetPositioned m -> n
f (Int -> m -> OffsetPositioned m
forall m. Int -> m -> OffsetPositioned m
OffsetPositioned Int
pos m
prime) n -> n -> n
forall a. Monoid a => a -> a -> a
`mappend` Int -> n
cont (Int -> Int
forall a. Enum a => a -> a
succ Int
pos))
   length :: OffsetPositioned m -> Int
length (OffsetPositioned Int
_ m
c) = m -> Int
forall m. Factorial m => m -> Int
length m
c
   reverse :: OffsetPositioned m -> OffsetPositioned m
reverse (OffsetPositioned Int
p m
c) = Int -> m -> OffsetPositioned m
forall m. Int -> m -> OffsetPositioned m
OffsetPositioned Int
p (m -> m
forall m. Factorial m => m -> m
Factorial.reverse m
c)
   {-# INLINE primePrefix #-}
   {-# INLINE foldl #-}
   {-# INLINE foldl' #-}
   {-# INLINE foldr #-}
   {-# INLINE foldMap #-}

instance (StableFactorial m, FactorialMonoid m) => FactorialMonoid (OffsetPositioned m) where
   splitPrimePrefix :: OffsetPositioned m
-> Maybe (OffsetPositioned m, OffsetPositioned m)
splitPrimePrefix (OffsetPositioned Int
p m
c) = ((m, m) -> (OffsetPositioned m, OffsetPositioned m))
-> Maybe (m, m) -> Maybe (OffsetPositioned m, OffsetPositioned m)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (m, m) -> (OffsetPositioned m, OffsetPositioned m)
forall m m.
MonoidNull m =>
(m, m) -> (OffsetPositioned m, OffsetPositioned m)
rewrap (m -> Maybe (m, m)
forall m. FactorialMonoid m => m -> Maybe (m, m)
splitPrimePrefix m
c)
      where rewrap :: (m, m) -> (OffsetPositioned m, OffsetPositioned m)
rewrap (m
cp, m
cs) = (Int -> m -> OffsetPositioned m
forall m. Int -> m -> OffsetPositioned m
OffsetPositioned Int
p m
cp, Int -> m -> OffsetPositioned m
forall m. Int -> m -> OffsetPositioned m
OffsetPositioned (if m -> Bool
forall m. MonoidNull m => m -> Bool
null m
cs then Int
0 else Int -> Int
forall a. Enum a => a -> a
succ Int
p) m
cs)
   splitPrimeSuffix :: OffsetPositioned m
-> Maybe (OffsetPositioned m, OffsetPositioned m)
splitPrimeSuffix (OffsetPositioned Int
p m
c) = ((m, m) -> (OffsetPositioned m, OffsetPositioned m))
-> Maybe (m, m) -> Maybe (OffsetPositioned m, OffsetPositioned m)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (m, m) -> (OffsetPositioned m, OffsetPositioned m)
forall m m.
Factorial m =>
(m, m) -> (OffsetPositioned m, OffsetPositioned m)
rewrap (m -> Maybe (m, m)
forall m. FactorialMonoid m => m -> Maybe (m, m)
splitPrimeSuffix m
c)
      where rewrap :: (m, m) -> (OffsetPositioned m, OffsetPositioned m)
rewrap (m
cp, m
cs) = (Int -> m -> OffsetPositioned m
forall m. Int -> m -> OffsetPositioned m
OffsetPositioned Int
p m
cp, Int -> m -> OffsetPositioned m
forall m. Int -> m -> OffsetPositioned m
OffsetPositioned (Int
p Int -> Int -> Int
forall a. Num a => a -> a -> a
+ m -> Int
forall m. Factorial m => m -> Int
length m
cp) m
cs)
   spanMaybe :: s
-> (s -> OffsetPositioned m -> Maybe s)
-> OffsetPositioned m
-> (OffsetPositioned m, OffsetPositioned m, s)
spanMaybe s
s0 s -> OffsetPositioned m -> Maybe s
f (OffsetPositioned Int
p0 m
t) = (m, m, (s, Int)) -> (OffsetPositioned m, OffsetPositioned m, s)
forall m m c.
(m, m, (c, Int)) -> (OffsetPositioned m, OffsetPositioned m, c)
rewrap ((m, m, (s, Int)) -> (OffsetPositioned m, OffsetPositioned m, s))
-> (m, m, (s, Int)) -> (OffsetPositioned m, OffsetPositioned m, s)
forall a b. (a -> b) -> a -> b
$ (s, Int)
-> ((s, Int) -> m -> Maybe (s, Int)) -> m -> (m, m, (s, Int))
forall m s.
FactorialMonoid m =>
s -> (s -> m -> Maybe s) -> m -> (m, m, s)
Factorial.spanMaybe (s
s0, Int
p0) (s, Int) -> m -> Maybe (s, Int)
f' m
t
      where f' :: (s, Int) -> m -> Maybe (s, Int)
f' (s
s, Int
p) m
prime = do s
s' <- s -> OffsetPositioned m -> Maybe s
f s
s (Int -> m -> OffsetPositioned m
forall m. Int -> m -> OffsetPositioned m
OffsetPositioned Int
p m
prime)
                                 let p' :: Int
p' = Int -> Int
forall a. Enum a => a -> a
succ Int
p
                                 (s, Int) -> Maybe (s, Int)
forall a. a -> Maybe a
Just ((s, Int) -> Maybe (s, Int)) -> (s, Int) -> Maybe (s, Int)
forall a b. (a -> b) -> a -> b
$! Int -> (s, Int) -> (s, Int)
seq Int
p' (s
s', Int
p')
            rewrap :: (m, m, (c, Int)) -> (OffsetPositioned m, OffsetPositioned m, c)
rewrap (m
prefix, m
suffix, (c
s, Int
p)) = (Int -> m -> OffsetPositioned m
forall m. Int -> m -> OffsetPositioned m
OffsetPositioned Int
p0 m
prefix, Int -> m -> OffsetPositioned m
forall m. Int -> m -> OffsetPositioned m
OffsetPositioned Int
p m
suffix, c
s)
   spanMaybe' :: s
-> (s -> OffsetPositioned m -> Maybe s)
-> OffsetPositioned m
-> (OffsetPositioned m, OffsetPositioned m, s)
spanMaybe' s
s0 s -> OffsetPositioned m -> Maybe s
f (OffsetPositioned Int
p0 m
t) = (m, m, (s, Int)) -> (OffsetPositioned m, OffsetPositioned m, s)
forall m m c.
(m, m, (c, Int)) -> (OffsetPositioned m, OffsetPositioned m, c)
rewrap ((m, m, (s, Int)) -> (OffsetPositioned m, OffsetPositioned m, s))
-> (m, m, (s, Int)) -> (OffsetPositioned m, OffsetPositioned m, s)
forall a b. (a -> b) -> a -> b
$! (s, Int)
-> ((s, Int) -> m -> Maybe (s, Int)) -> m -> (m, m, (s, Int))
forall m s.
FactorialMonoid m =>
s -> (s -> m -> Maybe s) -> m -> (m, m, s)
Factorial.spanMaybe' (s
s0, Int
p0) (s, Int) -> m -> Maybe (s, Int)
f' m
t
      where f' :: (s, Int) -> m -> Maybe (s, Int)
f' (s
s, Int
p) m
prime = do s
s' <- s -> OffsetPositioned m -> Maybe s
f s
s (Int -> m -> OffsetPositioned m
forall m. Int -> m -> OffsetPositioned m
OffsetPositioned Int
p m
prime)
                                 let p' :: Int
p' = Int -> Int
forall a. Enum a => a -> a
succ Int
p
                                 (s, Int) -> Maybe (s, Int)
forall a. a -> Maybe a
Just ((s, Int) -> Maybe (s, Int)) -> (s, Int) -> Maybe (s, Int)
forall a b. (a -> b) -> a -> b
$! s
s' s -> (s, Int) -> (s, Int)
`seq` Int
p' Int -> (s, Int) -> (s, Int)
`seq` (s
s', Int
p')
            rewrap :: (m, m, (c, Int)) -> (OffsetPositioned m, OffsetPositioned m, c)
rewrap (m
prefix, m
suffix, (c
s, Int
p)) = (Int -> m -> OffsetPositioned m
forall m. Int -> m -> OffsetPositioned m
OffsetPositioned Int
p0 m
prefix, Int -> m -> OffsetPositioned m
forall m. Int -> m -> OffsetPositioned m
OffsetPositioned Int
p m
suffix, c
s)
   span :: (OffsetPositioned m -> Bool)
-> OffsetPositioned m -> (OffsetPositioned m, OffsetPositioned m)
span OffsetPositioned m -> Bool
f (OffsetPositioned Int
p0 m
t) = (m, m, Int) -> (OffsetPositioned m, OffsetPositioned m)
forall m m. (m, m, Int) -> (OffsetPositioned m, OffsetPositioned m)
rewrap ((m, m, Int) -> (OffsetPositioned m, OffsetPositioned m))
-> (m, m, Int) -> (OffsetPositioned m, OffsetPositioned m)
forall a b. (a -> b) -> a -> b
$ Int -> (Int -> m -> Maybe Int) -> m -> (m, m, Int)
forall m s.
FactorialMonoid m =>
s -> (s -> m -> Maybe s) -> m -> (m, m, s)
Factorial.spanMaybe' Int
p0 Int -> m -> Maybe Int
f' m
t
      where f' :: Int -> m -> Maybe Int
f' Int
p m
prime = if OffsetPositioned m -> Bool
f (Int -> m -> OffsetPositioned m
forall m. Int -> m -> OffsetPositioned m
OffsetPositioned Int
p m
prime)
                         then Int -> Maybe Int
forall a. a -> Maybe a
Just (Int -> Maybe Int) -> Int -> Maybe Int
forall a b. (a -> b) -> a -> b
$! Int -> Int
forall a. Enum a => a -> a
succ Int
p
                         else Maybe Int
forall a. Maybe a
Nothing
            rewrap :: (m, m, Int) -> (OffsetPositioned m, OffsetPositioned m)
rewrap (m
prefix, m
suffix, Int
p) = (Int -> m -> OffsetPositioned m
forall m. Int -> m -> OffsetPositioned m
OffsetPositioned Int
p0 m
prefix, Int -> m -> OffsetPositioned m
forall m. Int -> m -> OffsetPositioned m
OffsetPositioned Int
p m
suffix)
   splitAt :: Int
-> OffsetPositioned m -> (OffsetPositioned m, OffsetPositioned m)
splitAt Int
n m :: OffsetPositioned m
m@(OffsetPositioned Int
p m
c) | Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
0 = (OffsetPositioned m
forall a. Monoid a => a
mempty, OffsetPositioned m
m)
                                      | Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= m -> Int
forall m. Factorial m => m -> Int
length m
c = (OffsetPositioned m
m, OffsetPositioned m
forall a. Monoid a => a
mempty)
                                      | Bool
otherwise = (Int -> m -> OffsetPositioned m
forall m. Int -> m -> OffsetPositioned m
OffsetPositioned Int
p m
prefix, Int -> m -> OffsetPositioned m
forall m. Int -> m -> OffsetPositioned m
OffsetPositioned (Int
p Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
n) m
suffix)
      where (m
prefix, m
suffix) = Int -> m -> (m, m)
forall m. FactorialMonoid m => Int -> m -> (m, m)
splitAt Int
n m
c
   drop :: Int -> OffsetPositioned m -> OffsetPositioned m
drop Int
n (OffsetPositioned Int
p m
c) = Int -> m -> OffsetPositioned m
forall m. Int -> m -> OffsetPositioned m
OffsetPositioned (Int
p Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
n) (Int -> m -> m
forall m. FactorialMonoid m => Int -> m -> m
Factorial.drop Int
n m
c)
   take :: Int -> OffsetPositioned m -> OffsetPositioned m
take Int
n (OffsetPositioned Int
p m
c) = Int -> m -> OffsetPositioned m
forall m. Int -> m -> OffsetPositioned m
OffsetPositioned Int
p (Int -> m -> m
forall m. FactorialMonoid m => Int -> m -> m
Factorial.take Int
n m
c)
   {-# INLINE splitPrimePrefix #-}
   {-# INLINE splitPrimeSuffix #-}
   {-# INLINE span #-}
   {-# INLINE splitAt #-}
   {-# INLINE take #-}
   {-# INLINE drop #-}

instance (StableFactorial m, TextualMonoid m) => Factorial (LinePositioned m) where
   factors :: LinePositioned m -> [LinePositioned m]
factors (LinePositioned Int
p0 Int
l0 Int
lp0 m
c) = ((Int, Int, Int), [LinePositioned m]) -> [LinePositioned m]
forall a b. (a, b) -> b
snd (((Int, Int, Int), [LinePositioned m]) -> [LinePositioned m])
-> ((Int, Int, Int), [LinePositioned m]) -> [LinePositioned m]
forall a b. (a -> b) -> a -> b
$ ((Int, Int, Int) -> m -> ((Int, Int, Int), LinePositioned m))
-> (Int, Int, Int) -> [m] -> ((Int, Int, Int), [LinePositioned m])
forall (t :: * -> *) a b c.
Traversable t =>
(a -> b -> (a, c)) -> a -> t b -> (a, t c)
List.mapAccumL (Int, Int, Int) -> m -> ((Int, Int, Int), LinePositioned m)
forall m.
TextualMonoid m =>
(Int, Int, Int) -> m -> ((Int, Int, Int), LinePositioned m)
next (Int
p0, Int
l0, Int
lp0) (m -> [m]
forall m. Factorial m => m -> [m]
factors m
c)
      where next :: (Int, Int, Int) -> m -> ((Int, Int, Int), LinePositioned m)
next (Int
p, Int
l, Int
lp) m
c1 = let p' :: Int
p' = Int -> Int
forall a. Enum a => a -> a
succ Int
p
                                 in Int
p' Int
-> ((Int, Int, Int), LinePositioned m)
-> ((Int, Int, Int), LinePositioned m)
`seq` case m -> Maybe Char
forall t. TextualMonoid t => t -> Maybe Char
characterPrefix m
c1
                                             of Just Char
'\n' -> ((Int
p', Int -> Int
forall a. Enum a => a -> a
succ Int
l, Int
p), Int -> Int -> Int -> m -> LinePositioned m
forall m. Int -> Int -> Int -> m -> LinePositioned m
LinePositioned Int
p Int
l Int
lp m
c1)
                                                Just Char
'\f' -> ((Int
p', Int -> Int
forall a. Enum a => a -> a
succ Int
l, Int
p), Int -> Int -> Int -> m -> LinePositioned m
forall m. Int -> Int -> Int -> m -> LinePositioned m
LinePositioned Int
p Int
l Int
lp m
c1)
                                                Just Char
'\r' -> ((Int
p', Int
l, Int
p), Int -> Int -> Int -> m -> LinePositioned m
forall m. Int -> Int -> Int -> m -> LinePositioned m
LinePositioned Int
p Int
l Int
lp m
c1)
                                                Just Char
'\t' -> ((Int
p', Int
l, Int
lp Int -> Int -> Int
forall a. Num a => a -> a -> a
+ (Int
p Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
lp) Int -> Int -> Int
forall a. Integral a => a -> a -> a
`mod` Int
8 Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
8), Int -> Int -> Int -> m -> LinePositioned m
forall m. Int -> Int -> Int -> m -> LinePositioned m
LinePositioned Int
p Int
l Int
lp m
c1)
                                                Maybe Char
_ -> ((Int
p', Int
l, Int
lp), Int -> Int -> Int -> m -> LinePositioned m
forall m. Int -> Int -> Int -> m -> LinePositioned m
LinePositioned Int
p Int
l Int
lp m
c1)
   primePrefix :: LinePositioned m -> LinePositioned m
primePrefix (LinePositioned Int
p Int
l Int
lp m
c) = Int -> Int -> Int -> m -> LinePositioned m
forall m. Int -> Int -> Int -> m -> LinePositioned m
LinePositioned Int
p Int
l Int
lp (m -> m
forall m. Factorial m => m -> m
primePrefix m
c)
   foldl :: (a -> LinePositioned m -> a) -> a -> LinePositioned m -> a
foldl a -> LinePositioned m -> a
f a
a0 (LinePositioned Int
p0 Int
l0 Int
lp0 m
c0) = (a, Int, Int, Int) -> a
forall a b c d. (a, b, c, d) -> a
fstOf4 ((a, Int, Int, Int) -> a) -> (a, Int, Int, Int) -> a
forall a b. (a -> b) -> a -> b
$! ((a, Int, Int, Int) -> m -> (a, Int, Int, Int))
-> (a, Int, Int, Int) -> m -> (a, Int, Int, Int)
forall m a. Factorial m => (a -> m -> a) -> a -> m -> a
Factorial.foldl (a, Int, Int, Int) -> m -> (a, Int, Int, Int)
f' (a
a0, Int
p0, Int
l0, Int
lp0) m
c0
      where f' :: (a, Int, Int, Int) -> m -> (a, Int, Int, Int)
f' (a
a, Int
p, Int
l, Int
lp) m
c = case m -> Maybe Char
forall t. TextualMonoid t => t -> Maybe Char
characterPrefix m
c
                                 of Just Char
'\n' -> (a -> LinePositioned m -> a
f a
a (Int -> Int -> Int -> m -> LinePositioned m
forall m. Int -> Int -> Int -> m -> LinePositioned m
LinePositioned Int
p Int
l Int
lp m
c), Int -> Int
forall a. Enum a => a -> a
succ Int
p, Int -> Int
forall a. Enum a => a -> a
succ Int
l, Int
p)
                                    Just Char
'\f' -> (a -> LinePositioned m -> a
f a
a (Int -> Int -> Int -> m -> LinePositioned m
forall m. Int -> Int -> Int -> m -> LinePositioned m
LinePositioned Int
p Int
l Int
lp m
c), Int -> Int
forall a. Enum a => a -> a
succ Int
p, Int -> Int
forall a. Enum a => a -> a
succ Int
l, Int
p)
                                    Just Char
'\r' -> (a -> LinePositioned m -> a
f a
a (Int -> Int -> Int -> m -> LinePositioned m
forall m. Int -> Int -> Int -> m -> LinePositioned m
LinePositioned Int
p Int
l Int
lp m
c), Int -> Int
forall a. Enum a => a -> a
succ Int
p, Int
l, Int
p)
                                    Just Char
'\t' -> (a -> LinePositioned m -> a
f a
a (Int -> Int -> Int -> m -> LinePositioned m
forall m. Int -> Int -> Int -> m -> LinePositioned m
LinePositioned Int
p Int
l Int
lp m
c), Int -> Int
forall a. Enum a => a -> a
succ Int
p, Int
l, Int
lp Int -> Int -> Int
forall a. Num a => a -> a -> a
+ (Int
p Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
lp) Int -> Int -> Int
forall a. Integral a => a -> a -> a
`mod` Int
8 Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
8)
                                    Maybe Char
_ -> (a -> LinePositioned m -> a
f a
a (Int -> Int -> Int -> m -> LinePositioned m
forall m. Int -> Int -> Int -> m -> LinePositioned m
LinePositioned Int
p Int
l Int
lp m
c), Int -> Int
forall a. Enum a => a -> a
succ Int
p, Int
l, Int
lp)
   foldl' :: (a -> LinePositioned m -> a) -> a -> LinePositioned m -> a
foldl' a -> LinePositioned m -> a
f a
a0 (LinePositioned Int
p0 Int
l0 Int
lp0 m
c0) = (a, Int, Int, Int) -> a
forall a b c d. (a, b, c, d) -> a
fstOf4 ((a, Int, Int, Int) -> a) -> (a, Int, Int, Int) -> a
forall a b. (a -> b) -> a -> b
$! ((a, Int, Int, Int) -> m -> (a, Int, Int, Int))
-> (a, Int, Int, Int) -> m -> (a, Int, Int, Int)
forall m a. Factorial m => (a -> m -> a) -> a -> m -> a
Factorial.foldl' (a, Int, Int, Int) -> m -> (a, Int, Int, Int)
f' (a
a0, Int
p0, Int
l0, Int
lp0) m
c0
      where f' :: (a, Int, Int, Int) -> m -> (a, Int, Int, Int)
f' (a
a, Int
p, Int
l, Int
lp) m
c = let a' :: a
a' = a -> LinePositioned m -> a
f a
a (Int -> Int -> Int -> m -> LinePositioned m
forall m. Int -> Int -> Int -> m -> LinePositioned m
LinePositioned Int
p Int
l Int
lp m
c)
                                 in a -> (a, Int, Int, Int) -> (a, Int, Int, Int)
seq a
a' (case m -> Maybe Char
forall t. TextualMonoid t => t -> Maybe Char
characterPrefix m
c
                                            of Just Char
'\n' -> (a
a', Int -> Int
forall a. Enum a => a -> a
succ Int
p, Int -> Int
forall a. Enum a => a -> a
succ Int
l, Int
p)
                                               Just Char
'\f' -> (a
a', Int -> Int
forall a. Enum a => a -> a
succ Int
p, Int -> Int
forall a. Enum a => a -> a
succ Int
l, Int
p)
                                               Just Char
'\r' -> (a
a', Int -> Int
forall a. Enum a => a -> a
succ Int
p, Int
l, Int
p)
                                               Just Char
'\t' -> (a
a', Int -> Int
forall a. Enum a => a -> a
succ Int
p, Int
l, Int
lp Int -> Int -> Int
forall a. Num a => a -> a -> a
+ (Int
p Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
lp) Int -> Int -> Int
forall a. Integral a => a -> a -> a
`mod` Int
8 Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
8)
                                               Maybe Char
_ -> (a
a', Int -> Int
forall a. Enum a => a -> a
succ Int
p, Int
l, Int
lp))
   foldr :: (LinePositioned m -> a -> a) -> a -> LinePositioned m -> a
foldr LinePositioned m -> a -> a
f a
a0 (LinePositioned Int
p0 Int
l0 Int
lp0 m
c0) = (m -> (Int -> Int -> Int -> a) -> Int -> Int -> Int -> a)
-> (Int -> Int -> Int -> a) -> m -> Int -> Int -> Int -> a
forall m a. Factorial m => (m -> a -> a) -> a -> m -> a
Factorial.foldr m -> (Int -> Int -> Int -> a) -> Int -> Int -> Int -> a
f' (a -> Int -> Int -> Int -> a
forall a b c d. a -> b -> c -> d -> a
const3 a
a0) m
c0 Int
p0 Int
l0 Int
lp0
      where f' :: m -> (Int -> Int -> Int -> a) -> Int -> Int -> Int -> a
f' m
c Int -> Int -> Int -> a
cont Int
p Int
l Int
lp = case m -> Maybe Char
forall t. TextualMonoid t => t -> Maybe Char
characterPrefix m
c
                               of Just Char
'\n' -> LinePositioned m -> a -> a
f (Int -> Int -> Int -> m -> LinePositioned m
forall m. Int -> Int -> Int -> m -> LinePositioned m
LinePositioned Int
p Int
l Int
lp m
c) (a -> a) -> a -> a
forall a b. (a -> b) -> a -> b
$ ((Int -> Int -> Int -> a
cont (Int -> Int -> Int -> a) -> Int -> Int -> Int -> a
forall a b. (a -> b) -> a -> b
$! Int -> Int
forall a. Enum a => a -> a
succ Int
p) (Int -> Int -> a) -> Int -> Int -> a
forall a b. (a -> b) -> a -> b
$! Int -> Int
forall a. Enum a => a -> a
succ Int
l) Int
p
                                  Just Char
'\f' -> LinePositioned m -> a -> a
f (Int -> Int -> Int -> m -> LinePositioned m
forall m. Int -> Int -> Int -> m -> LinePositioned m
LinePositioned Int
p Int
l Int
lp m
c) (a -> a) -> a -> a
forall a b. (a -> b) -> a -> b
$ ((Int -> Int -> Int -> a
cont (Int -> Int -> Int -> a) -> Int -> Int -> Int -> a
forall a b. (a -> b) -> a -> b
$! Int -> Int
forall a. Enum a => a -> a
succ Int
p) (Int -> Int -> a) -> Int -> Int -> a
forall a b. (a -> b) -> a -> b
$! Int -> Int
forall a. Enum a => a -> a
succ Int
l) Int
p
                                  Just Char
'\r' -> LinePositioned m -> a -> a
f (Int -> Int -> Int -> m -> LinePositioned m
forall m. Int -> Int -> Int -> m -> LinePositioned m
LinePositioned Int
p Int
l Int
lp m
c) (a -> a) -> a -> a
forall a b. (a -> b) -> a -> b
$ (Int -> Int -> Int -> a
cont (Int -> Int -> Int -> a) -> Int -> Int -> Int -> a
forall a b. (a -> b) -> a -> b
$! Int -> Int
forall a. Enum a => a -> a
succ Int
p) Int
l Int
p
                                  Just Char
'\t' -> LinePositioned m -> a -> a
f (Int -> Int -> Int -> m -> LinePositioned m
forall m. Int -> Int -> Int -> m -> LinePositioned m
LinePositioned Int
p Int
l Int
lp m
c) (a -> a) -> a -> a
forall a b. (a -> b) -> a -> b
$ (Int -> Int -> Int -> a
cont (Int -> Int -> Int -> a) -> Int -> Int -> Int -> a
forall a b. (a -> b) -> a -> b
$! Int -> Int
forall a. Enum a => a -> a
succ Int
p) Int
l (Int -> a) -> Int -> a
forall a b. (a -> b) -> a -> b
$! Int
lp Int -> Int -> Int
forall a. Num a => a -> a -> a
+ (Int
p Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
lp) Int -> Int -> Int
forall a. Integral a => a -> a -> a
`mod` Int
8 Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
8
                                  Maybe Char
_ -> LinePositioned m -> a -> a
f (Int -> Int -> Int -> m -> LinePositioned m
forall m. Int -> Int -> Int -> m -> LinePositioned m
LinePositioned Int
p Int
l Int
lp m
c) (a -> a) -> a -> a
forall a b. (a -> b) -> a -> b
$ (Int -> Int -> Int -> a
cont (Int -> Int -> Int -> a) -> Int -> Int -> Int -> a
forall a b. (a -> b) -> a -> b
$! Int -> Int
forall a. Enum a => a -> a
succ Int
p) Int
l Int
lp
   foldMap :: (LinePositioned m -> n) -> LinePositioned m -> n
foldMap LinePositioned m -> n
f (LinePositioned Int
p0 Int
l0 Int
lp0 m
c) = Endo (Int -> Int -> Int -> n)
-> (Int -> Int -> Int -> n) -> Int -> Int -> Int -> n
forall a. Endo a -> a -> a
appEndo ((m -> Endo (Int -> Int -> Int -> n))
-> m -> Endo (Int -> Int -> Int -> n)
forall m n. (Factorial m, Monoid n) => (m -> n) -> m -> n
Factorial.foldMap m -> Endo (Int -> Int -> Int -> n)
f' m
c) ((Int -> Int -> n) -> Int -> Int -> Int -> n
forall a b. a -> b -> a
const Int -> Int -> n
forall a. Monoid a => a
mempty) Int
p0 Int
l0 Int
lp0
      where -- f' :: m -> Endo (Int -> Int -> Int -> m)
            f' :: m -> Endo (Int -> Int -> Int -> n)
f' m
prime = ((Int -> Int -> Int -> n) -> Int -> Int -> Int -> n)
-> Endo (Int -> Int -> Int -> n)
forall a. (a -> a) -> Endo a
Endo (\Int -> Int -> Int -> n
cont Int
p Int
l Int
lp-> LinePositioned m -> n
f (Int -> Int -> Int -> m -> LinePositioned m
forall m. Int -> Int -> Int -> m -> LinePositioned m
LinePositioned Int
p Int
l Int
lp m
prime)
                                            n -> n -> n
forall a. Monoid a => a -> a -> a
`mappend`
                                            case m -> Maybe Char
forall t. TextualMonoid t => t -> Maybe Char
characterPrefix m
prime
                                            of Just Char
'\n' -> Int -> Int -> Int -> n
cont (Int -> Int
forall a. Enum a => a -> a
succ Int
p) (Int -> Int
forall a. Enum a => a -> a
succ Int
l) Int
p
                                               Just Char
'\f' -> Int -> Int -> Int -> n
cont (Int -> Int
forall a. Enum a => a -> a
succ Int
p) (Int -> Int
forall a. Enum a => a -> a
succ Int
l) Int
p
                                               Just Char
'\r' -> Int -> Int -> Int -> n
cont (Int -> Int
forall a. Enum a => a -> a
succ Int
p) Int
l Int
p
                                               Just Char
'\t' -> Int -> Int -> Int -> n
cont (Int -> Int
forall a. Enum a => a -> a
succ Int
p) Int
l (Int
lp Int -> Int -> Int
forall a. Num a => a -> a -> a
+ (Int
p Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
lp) Int -> Int -> Int
forall a. Integral a => a -> a -> a
`mod` Int
8 Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
8)
                                               Maybe Char
_ -> Int -> Int -> Int -> n
cont (Int -> Int
forall a. Enum a => a -> a
succ Int
p) Int
l Int
lp)
   length :: LinePositioned m -> Int
length = m -> Int
forall m. Factorial m => m -> Int
length (m -> Int) -> (LinePositioned m -> m) -> LinePositioned m -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. LinePositioned m -> m
forall a. LinePositioned a -> a
extractLines
   reverse :: LinePositioned m -> LinePositioned m
reverse (LinePositioned Int
p Int
l Int
lp m
c) = Int -> Int -> Int -> m -> LinePositioned m
forall m. Int -> Int -> Int -> m -> LinePositioned m
LinePositioned Int
p Int
l Int
lp (m -> m
forall m. Factorial m => m -> m
Factorial.reverse m
c)
   {-# INLINE primePrefix #-}
   {-# INLINE foldl #-}
   {-# INLINE foldl' #-}
   {-# INLINE foldr #-}
   {-# INLINE foldMap #-}
   {-# INLINE length #-}
   {-# INLINE reverse #-}

instance (StableFactorial m, TextualMonoid m) => FactorialMonoid (LinePositioned m) where
   splitPrimePrefix :: LinePositioned m -> Maybe (LinePositioned m, LinePositioned m)
splitPrimePrefix (LinePositioned Int
p Int
l Int
lp m
c) = ((m, m) -> (LinePositioned m, LinePositioned m))
-> Maybe (m, m) -> Maybe (LinePositioned m, LinePositioned m)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (m, m) -> (LinePositioned m, LinePositioned m)
forall m t.
(StableFactorial m, TextualMonoid m, TextualMonoid t) =>
(t, m) -> (LinePositioned t, LinePositioned m)
rewrap (m -> Maybe (m, m)
forall m. FactorialMonoid m => m -> Maybe (m, m)
splitPrimePrefix m
c)
      where rewrap :: (t, m) -> (LinePositioned t, LinePositioned m)
rewrap (t
cp, m
cs) = (Int -> Int -> Int -> t -> LinePositioned t
forall m. Int -> Int -> Int -> m -> LinePositioned m
LinePositioned Int
p Int
l Int
lp t
cp,
                               if m -> Bool
forall m. MonoidNull m => m -> Bool
null m
cs then LinePositioned m
forall a. Monoid a => a
mempty
                               else case t -> Maybe Char
forall t. TextualMonoid t => t -> Maybe Char
characterPrefix t
cp
                                    of Just Char
'\n' -> Int -> Int -> Int -> m -> LinePositioned m
forall m. Int -> Int -> Int -> m -> LinePositioned m
LinePositioned Int
p' (Int -> Int
forall a. Enum a => a -> a
succ Int
l) Int
p m
cs
                                       Just Char
'\f' -> Int -> Int -> Int -> m -> LinePositioned m
forall m. Int -> Int -> Int -> m -> LinePositioned m
LinePositioned Int
p' (Int -> Int
forall a. Enum a => a -> a
succ Int
l) Int
p m
cs
                                       Just Char
'\r' -> Int -> Int -> Int -> m -> LinePositioned m
forall m. Int -> Int -> Int -> m -> LinePositioned m
LinePositioned Int
p' Int
l Int
p m
cs
                                       Just Char
'\t' -> Int -> Int -> Int -> m -> LinePositioned m
forall m. Int -> Int -> Int -> m -> LinePositioned m
LinePositioned Int
p' Int
l (Int
lp Int -> Int -> Int
forall a. Num a => a -> a -> a
+ (Int
p Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
lp) Int -> Int -> Int
forall a. Integral a => a -> a -> a
`mod` Int
8 Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
8) m
cs
                                       Maybe Char
_ -> Int -> Int -> Int -> m -> LinePositioned m
forall m. Int -> Int -> Int -> m -> LinePositioned m
LinePositioned Int
p' Int
l Int
lp m
cs)
            p' :: Int
p' = Int -> Int
forall a. Enum a => a -> a
succ Int
p
   splitPrimeSuffix :: LinePositioned m -> Maybe (LinePositioned m, LinePositioned m)
splitPrimeSuffix (LinePositioned Int
p Int
l Int
lp m
c) = ((m, m) -> (LinePositioned m, LinePositioned m))
-> Maybe (m, m) -> Maybe (LinePositioned m, LinePositioned m)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (m, m) -> (LinePositioned m, LinePositioned m)
forall m m.
TextualMonoid m =>
(m, m) -> (LinePositioned m, LinePositioned m)
rewrap (m -> Maybe (m, m)
forall m. FactorialMonoid m => m -> Maybe (m, m)
splitPrimeSuffix m
c)
      where rewrap :: (m, m) -> (LinePositioned m, LinePositioned m)
rewrap (m
cp, m
cs) = (Int -> Int -> Int -> m -> LinePositioned m
forall m. Int -> Int -> Int -> m -> LinePositioned m
LinePositioned Int
p Int
l Int
lp m
cp, Int -> Int -> Int -> m -> LinePositioned m
forall m. Int -> Int -> Int -> m -> LinePositioned m
LinePositioned Int
p' (Int
l Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
lines) (Int
p' Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
columns) m
cs)
               where len :: Int
len = m -> Int
forall m. Factorial m => m -> Int
length m
cp
                     (Int
lines, Int
columns) = m -> (Int, Int)
forall m. TextualMonoid m => m -> (Int, Int)
linesColumns m
cp
                     p' :: Int
p' = Int
p Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
len
   spanMaybe :: s
-> (s -> LinePositioned m -> Maybe s)
-> LinePositioned m
-> (LinePositioned m, LinePositioned m, s)
spanMaybe s
s0 s -> LinePositioned m -> Maybe s
f (LinePositioned Int
p0 Int
l0 Int
lp0 m
c) = (m, m, (s, Int, Int, Int))
-> (LinePositioned m, LinePositioned m, s)
forall m m c.
(m, m, (c, Int, Int, Int))
-> (LinePositioned m, LinePositioned m, c)
rewrap ((m, m, (s, Int, Int, Int))
 -> (LinePositioned m, LinePositioned m, s))
-> (m, m, (s, Int, Int, Int))
-> (LinePositioned m, LinePositioned m, s)
forall a b. (a -> b) -> a -> b
$ (s, Int, Int, Int)
-> ((s, Int, Int, Int) -> m -> Maybe (s, Int, Int, Int))
-> m
-> (m, m, (s, Int, Int, Int))
forall m s.
FactorialMonoid m =>
s -> (s -> m -> Maybe s) -> m -> (m, m, s)
Factorial.spanMaybe (s
s0, Int
p0, Int
l0, Int
lp0) (s, Int, Int, Int) -> m -> Maybe (s, Int, Int, Int)
f' m
c
      where f' :: (s, Int, Int, Int) -> m -> Maybe (s, Int, Int, Int)
f' (s
s, Int
p, Int
l, Int
lp) m
prime = do s
s' <- s -> LinePositioned m -> Maybe s
f s
s (Int -> Int -> Int -> m -> LinePositioned m
forall m. Int -> Int -> Int -> m -> LinePositioned m
LinePositioned Int
p Int
l Int
lp m
prime)
                                        let p' :: Int
p' = Int -> Int
forall a. Enum a => a -> a
succ Int
p
                                            l' :: Int
l' = Int -> Int
forall a. Enum a => a -> a
succ Int
l
                                        (s, Int, Int, Int) -> Maybe (s, Int, Int, Int)
forall a. a -> Maybe a
Just ((s, Int, Int, Int) -> Maybe (s, Int, Int, Int))
-> (s, Int, Int, Int) -> Maybe (s, Int, Int, Int)
forall a b. (a -> b) -> a -> b
$! Int
p' Int -> (s, Int, Int, Int) -> (s, Int, Int, Int)
`seq` case m -> Maybe Char
forall t. TextualMonoid t => t -> Maybe Char
characterPrefix m
prime
                                                         of Just Char
'\n' -> Int
l' Int -> (s, Int, Int, Int) -> (s, Int, Int, Int)
`seq` (s
s', Int
p', Int
l', Int
p)
                                                            Just Char
'\f' -> Int
l' Int -> (s, Int, Int, Int) -> (s, Int, Int, Int)
`seq` (s
s', Int
p', Int
l', Int
p)
                                                            Just Char
'\r' -> (s
s', Int
p', Int
l, Int
p)
                                                            Just Char
'\t' -> (s
s', Int
p', Int
l, Int
lp Int -> Int -> Int
forall a. Num a => a -> a -> a
+ (Int
p Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
lp) Int -> Int -> Int
forall a. Integral a => a -> a -> a
`mod` Int
8 Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
8)
                                                            Maybe Char
_ -> (s
s', Int
p', Int
l, Int
lp)
            rewrap :: (m, m, (c, Int, Int, Int))
-> (LinePositioned m, LinePositioned m, c)
rewrap (m
prefix, m
suffix, (c
s, Int
p, Int
l, Int
lp)) = (Int -> Int -> Int -> m -> LinePositioned m
forall m. Int -> Int -> Int -> m -> LinePositioned m
LinePositioned Int
p0 Int
l0 Int
lp0 m
prefix, Int -> Int -> Int -> m -> LinePositioned m
forall m. Int -> Int -> Int -> m -> LinePositioned m
LinePositioned Int
p Int
l Int
lp m
suffix, c
s)
   spanMaybe' :: s
-> (s -> LinePositioned m -> Maybe s)
-> LinePositioned m
-> (LinePositioned m, LinePositioned m, s)
spanMaybe' s
s0 s -> LinePositioned m -> Maybe s
f (LinePositioned Int
p0 Int
l0 Int
lp0 m
c) = (m, m, (s, Int, Int, Int))
-> (LinePositioned m, LinePositioned m, s)
forall m m c.
(m, m, (c, Int, Int, Int))
-> (LinePositioned m, LinePositioned m, c)
rewrap ((m, m, (s, Int, Int, Int))
 -> (LinePositioned m, LinePositioned m, s))
-> (m, m, (s, Int, Int, Int))
-> (LinePositioned m, LinePositioned m, s)
forall a b. (a -> b) -> a -> b
$! (s, Int, Int, Int)
-> ((s, Int, Int, Int) -> m -> Maybe (s, Int, Int, Int))
-> m
-> (m, m, (s, Int, Int, Int))
forall m s.
FactorialMonoid m =>
s -> (s -> m -> Maybe s) -> m -> (m, m, s)
Factorial.spanMaybe' (s
s0, Int
p0, Int
l0, Int
lp0) (s, Int, Int, Int) -> m -> Maybe (s, Int, Int, Int)
f' m
c
      where f' :: (s, Int, Int, Int) -> m -> Maybe (s, Int, Int, Int)
f' (s
s, Int
p, Int
l, Int
lp) m
prime = do s
s' <- s -> LinePositioned m -> Maybe s
f s
s (Int -> Int -> Int -> m -> LinePositioned m
forall m. Int -> Int -> Int -> m -> LinePositioned m
LinePositioned Int
p Int
l Int
lp m
prime)
                                        let p' :: Int
p' = Int -> Int
forall a. Enum a => a -> a
succ Int
p
                                            l' :: Int
l' = Int -> Int
forall a. Enum a => a -> a
succ Int
l
                                        (s, Int, Int, Int) -> Maybe (s, Int, Int, Int)
forall a. a -> Maybe a
Just ((s, Int, Int, Int) -> Maybe (s, Int, Int, Int))
-> (s, Int, Int, Int) -> Maybe (s, Int, Int, Int)
forall a b. (a -> b) -> a -> b
$! s
s' s -> (s, Int, Int, Int) -> (s, Int, Int, Int)
`seq` Int
p' Int -> (s, Int, Int, Int) -> (s, Int, Int, Int)
`seq` case m -> Maybe Char
forall t. TextualMonoid t => t -> Maybe Char
characterPrefix m
prime
                                                                  of Just Char
'\n' -> Int
l' Int -> (s, Int, Int, Int) -> (s, Int, Int, Int)
`seq` (s
s', Int
p', Int
l', Int
p)
                                                                     Just Char
'\f' -> Int
l' Int -> (s, Int, Int, Int) -> (s, Int, Int, Int)
`seq` (s
s', Int
p', Int
l', Int
p)
                                                                     Just Char
'\r' -> (s
s', Int
p', Int
l, Int
p)
                                                                     Just Char
'\t' -> (s
s', Int
p', Int
l, Int
lp Int -> Int -> Int
forall a. Num a => a -> a -> a
+ (Int
p Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
lp) Int -> Int -> Int
forall a. Integral a => a -> a -> a
`mod` Int
8 Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
8)
                                                                     Maybe Char
_ -> (s
s', Int
p', Int
l, Int
lp)
            rewrap :: (m, m, (c, Int, Int, Int))
-> (LinePositioned m, LinePositioned m, c)
rewrap (m
prefix, m
suffix, (c
s, Int
p, Int
l, Int
lp)) = (Int -> Int -> Int -> m -> LinePositioned m
forall m. Int -> Int -> Int -> m -> LinePositioned m
LinePositioned Int
p0 Int
l0 Int
lp0 m
prefix, Int -> Int -> Int -> m -> LinePositioned m
forall m. Int -> Int -> Int -> m -> LinePositioned m
LinePositioned Int
p Int
l Int
lp m
suffix, c
s)

   span :: (LinePositioned m -> Bool)
-> LinePositioned m -> (LinePositioned m, LinePositioned m)
span LinePositioned m -> Bool
f (LinePositioned Int
p0 Int
l0 Int
lp0 m
t) = (m, m, (Int, Int, Int)) -> (LinePositioned m, LinePositioned m)
forall m m.
(m, m, (Int, Int, Int)) -> (LinePositioned m, LinePositioned m)
rewrap ((m, m, (Int, Int, Int)) -> (LinePositioned m, LinePositioned m))
-> (m, m, (Int, Int, Int)) -> (LinePositioned m, LinePositioned m)
forall a b. (a -> b) -> a -> b
$ (Int, Int, Int)
-> ((Int, Int, Int) -> m -> Maybe (Int, Int, Int))
-> m
-> (m, m, (Int, Int, Int))
forall m s.
FactorialMonoid m =>
s -> (s -> m -> Maybe s) -> m -> (m, m, s)
Factorial.spanMaybe' (Int
p0, Int
l0, Int
lp0) (Int, Int, Int) -> m -> Maybe (Int, Int, Int)
f' m
t
      where f' :: (Int, Int, Int) -> m -> Maybe (Int, Int, Int)
f' (Int
p, Int
l, Int
lp) m
prime = if LinePositioned m -> Bool
f (Int -> Int -> Int -> m -> LinePositioned m
forall m. Int -> Int -> Int -> m -> LinePositioned m
LinePositioned Int
p Int
l Int
lp m
prime)
                                  then let p' :: Int
p' = Int -> Int
forall a. Enum a => a -> a
succ Int
p
                                           l' :: Int
l' = Int -> Int
forall a. Enum a => a -> a
succ Int
l
                                       in (Int, Int, Int) -> Maybe (Int, Int, Int)
forall a. a -> Maybe a
Just ((Int, Int, Int) -> Maybe (Int, Int, Int))
-> (Int, Int, Int) -> Maybe (Int, Int, Int)
forall a b. (a -> b) -> a -> b
$! Int
p' Int -> (Int, Int, Int) -> (Int, Int, Int)
`seq` case m -> Maybe Char
forall t. TextualMonoid t => t -> Maybe Char
characterPrefix m
prime
                                                           of Just Char
'\n' -> Int
l' Int -> (Int, Int, Int) -> (Int, Int, Int)
`seq` (Int
p', Int
l', Int
p)
                                                              Just Char
'\f' -> Int
l' Int -> (Int, Int, Int) -> (Int, Int, Int)
`seq` (Int
p', Int
l', Int
p)
                                                              Just Char
'\r' -> (Int
p', Int
l, Int
p)
                                                              Just Char
'\t' -> (Int
p', Int
l, Int
lp Int -> Int -> Int
forall a. Num a => a -> a -> a
+ (Int
p Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
lp) Int -> Int -> Int
forall a. Integral a => a -> a -> a
`mod` Int
8 Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
8)
                                                              Maybe Char
_ -> (Int
p', Int
l, Int
lp)
                                  else Maybe (Int, Int, Int)
forall a. Maybe a
Nothing
            rewrap :: (m, m, (Int, Int, Int)) -> (LinePositioned m, LinePositioned m)
rewrap (m
prefix, m
suffix, (Int
p, Int
l, Int
lp)) = (Int -> Int -> Int -> m -> LinePositioned m
forall m. Int -> Int -> Int -> m -> LinePositioned m
LinePositioned Int
p0 Int
l0 Int
lp0 m
prefix, Int -> Int -> Int -> m -> LinePositioned m
forall m. Int -> Int -> Int -> m -> LinePositioned m
LinePositioned Int
p Int
l Int
lp m
suffix)
   splitAt :: Int -> LinePositioned m -> (LinePositioned m, LinePositioned m)
splitAt Int
n m :: LinePositioned m
m@(LinePositioned Int
p Int
l Int
lp m
c) | Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
0 = (LinePositioned m
forall a. Monoid a => a
mempty, LinePositioned m
m)
                                         | Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= m -> Int
forall m. Factorial m => m -> Int
length m
c = (LinePositioned m
m, LinePositioned m
forall a. Monoid a => a
mempty)
                                         | Bool
otherwise = (Int -> Int -> Int -> m -> LinePositioned m
forall m. Int -> Int -> Int -> m -> LinePositioned m
LinePositioned Int
p Int
l Int
lp m
prefix,
                                                        Int -> Int -> Int -> m -> LinePositioned m
forall m. Int -> Int -> Int -> m -> LinePositioned m
LinePositioned Int
p' (Int
l Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
lines) (Int
p' Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
columns) m
suffix)
      where (m
prefix, m
suffix) = Int -> m -> (m, m)
forall m. FactorialMonoid m => Int -> m -> (m, m)
splitAt Int
n m
c
            (Int
lines, Int
columns) = m -> (Int, Int)
forall m. TextualMonoid m => m -> (Int, Int)
linesColumns m
prefix
            p' :: Int
p' = Int
p Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
n
   take :: Int -> LinePositioned m -> LinePositioned m
take Int
n (LinePositioned Int
p Int
l Int
lp m
c) = Int -> Int -> Int -> m -> LinePositioned m
forall m. Int -> Int -> Int -> m -> LinePositioned m
LinePositioned Int
p Int
l Int
lp (Int -> m -> m
forall m. FactorialMonoid m => Int -> m -> m
Factorial.take Int
n m
c)
   {-# INLINE splitPrimePrefix #-}
   {-# INLINE splitPrimeSuffix #-}
   {-# INLINE span #-}
   {-# INLINE splitAt #-}
   {-# INLINE take #-}

instance StableFactorial m => StableFactorial (OffsetPositioned m)

instance (StableFactorial m, TextualMonoid m) => StableFactorial (LinePositioned m)

instance IsString m => IsString (OffsetPositioned m) where
   fromString :: String -> OffsetPositioned m
fromString = m -> OffsetPositioned m
forall (f :: * -> *) a. Applicative f => a -> f a
pure (m -> OffsetPositioned m)
-> (String -> m) -> String -> OffsetPositioned m
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> m
forall a. IsString a => String -> a
fromString

instance IsString m => IsString (LinePositioned m) where
   fromString :: String -> LinePositioned m
fromString = m -> LinePositioned m
forall (f :: * -> *) a. Applicative f => a -> f a
pure (m -> LinePositioned m)
-> (String -> m) -> String -> LinePositioned m
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> m
forall a. IsString a => String -> a
fromString

instance (StableFactorial m, TextualMonoid m) => TextualMonoid (OffsetPositioned m) where
   splitCharacterPrefix :: OffsetPositioned m -> Maybe (Char, OffsetPositioned m)
splitCharacterPrefix (OffsetPositioned Int
p m
t) = ((Char, m) -> (Char, OffsetPositioned m))
-> Maybe (Char, m) -> Maybe (Char, OffsetPositioned m)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Char, m) -> (Char, OffsetPositioned m)
forall m a.
(FactorialMonoid m, StableFactorial m) =>
(a, m) -> (a, OffsetPositioned m)
rewrap (m -> Maybe (Char, m)
forall t. TextualMonoid t => t -> Maybe (Char, t)
splitCharacterPrefix m
t)
      where rewrap :: (a, m) -> (a, OffsetPositioned m)
rewrap (a
c, m
cs) = if m -> Bool
forall m. MonoidNull m => m -> Bool
null m
cs then (a
c, OffsetPositioned m
forall a. Monoid a => a
mempty) else (a
c, Int -> m -> OffsetPositioned m
forall m. Int -> m -> OffsetPositioned m
OffsetPositioned (Int -> Int
forall a. Enum a => a -> a
succ Int
p) m
cs)

   fromText :: Text -> OffsetPositioned m
fromText = m -> OffsetPositioned m
forall (f :: * -> *) a. Applicative f => a -> f a
pure (m -> OffsetPositioned m)
-> (Text -> m) -> Text -> OffsetPositioned m
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> m
forall t. TextualMonoid t => Text -> t
fromText
   singleton :: Char -> OffsetPositioned m
singleton = m -> OffsetPositioned m
forall (f :: * -> *) a. Applicative f => a -> f a
pure (m -> OffsetPositioned m)
-> (Char -> m) -> Char -> OffsetPositioned m
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> m
forall t. TextualMonoid t => Char -> t
singleton

   characterPrefix :: OffsetPositioned m -> Maybe Char
characterPrefix = m -> Maybe Char
forall t. TextualMonoid t => t -> Maybe Char
characterPrefix (m -> Maybe Char)
-> (OffsetPositioned m -> m) -> OffsetPositioned m -> Maybe Char
forall b c a. (b -> c) -> (a -> b) -> a -> c
. OffsetPositioned m -> m
forall a. OffsetPositioned a -> a
extractOffset

   map :: (Char -> Char) -> OffsetPositioned m -> OffsetPositioned m
map Char -> Char
f (OffsetPositioned Int
p m
c) = Int -> m -> OffsetPositioned m
forall m. Int -> m -> OffsetPositioned m
OffsetPositioned Int
p ((Char -> Char) -> m -> m
forall t. TextualMonoid t => (Char -> Char) -> t -> t
map Char -> Char
f m
c)
   concatMap :: (Char -> OffsetPositioned m)
-> OffsetPositioned m -> OffsetPositioned m
concatMap Char -> OffsetPositioned m
f (OffsetPositioned Int
p m
c) = Int -> m -> OffsetPositioned m
forall m. Int -> m -> OffsetPositioned m
OffsetPositioned Int
p ((Char -> m) -> m -> m
forall t. TextualMonoid t => (Char -> t) -> t -> t
concatMap (OffsetPositioned m -> m
forall a. OffsetPositioned a -> a
extractOffset (OffsetPositioned m -> m)
-> (Char -> OffsetPositioned m) -> Char -> m
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> OffsetPositioned m
f) m
c)
   all :: (Char -> Bool) -> OffsetPositioned m -> Bool
all Char -> Bool
p = (Char -> Bool) -> m -> Bool
forall t. TextualMonoid t => (Char -> Bool) -> t -> Bool
all Char -> Bool
p (m -> Bool)
-> (OffsetPositioned m -> m) -> OffsetPositioned m -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. OffsetPositioned m -> m
forall a. OffsetPositioned a -> a
extractOffset
   any :: (Char -> Bool) -> OffsetPositioned m -> Bool
any Char -> Bool
p = (Char -> Bool) -> m -> Bool
forall t. TextualMonoid t => (Char -> Bool) -> t -> Bool
any Char -> Bool
p (m -> Bool)
-> (OffsetPositioned m -> m) -> OffsetPositioned m -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. OffsetPositioned m -> m
forall a. OffsetPositioned a -> a
extractOffset

   foldl :: (a -> OffsetPositioned m -> a)
-> (a -> Char -> a) -> a -> OffsetPositioned m -> a
foldl a -> OffsetPositioned m -> a
ft a -> Char -> a
fc a
a0 (OffsetPositioned Int
p0 m
c0) = (a, Int) -> a
forall a b. (a, b) -> a
fst ((a, Int) -> a) -> (a, Int) -> a
forall a b. (a -> b) -> a -> b
$ ((a, Int) -> m -> (a, Int))
-> ((a, Int) -> Char -> (a, Int)) -> (a, Int) -> m -> (a, Int)
forall t a.
TextualMonoid t =>
(a -> t -> a) -> (a -> Char -> a) -> a -> t -> a
Textual.foldl (a, Int) -> m -> (a, Int)
ft' (a, Int) -> Char -> (a, Int)
forall b. Enum b => (a, b) -> Char -> (a, b)
fc' (a
a0, Int
p0) m
c0
      where ft' :: (a, Int) -> m -> (a, Int)
ft' (a
a, Int
p) m
c = (a -> OffsetPositioned m -> a
ft a
a (Int -> m -> OffsetPositioned m
forall m. Int -> m -> OffsetPositioned m
OffsetPositioned Int
p m
c), Int -> Int
forall a. Enum a => a -> a
succ Int
p)
            fc' :: (a, b) -> Char -> (a, b)
fc' (a
a, b
p) Char
c = (a -> Char -> a
fc a
a Char
c, b -> b
forall a. Enum a => a -> a
succ b
p)
   foldl' :: (a -> OffsetPositioned m -> a)
-> (a -> Char -> a) -> a -> OffsetPositioned m -> a
foldl' a -> OffsetPositioned m -> a
ft a -> Char -> a
fc a
a0 (OffsetPositioned Int
p0 m
c0) = (a, Int) -> a
forall a b. (a, b) -> a
fst ((a, Int) -> a) -> (a, Int) -> a
forall a b. (a -> b) -> a -> b
$ ((a, Int) -> m -> (a, Int))
-> ((a, Int) -> Char -> (a, Int)) -> (a, Int) -> m -> (a, Int)
forall t a.
TextualMonoid t =>
(a -> t -> a) -> (a -> Char -> a) -> a -> t -> a
Textual.foldl' (a, Int) -> m -> (a, Int)
ft' (a, Int) -> Char -> (a, Int)
forall b. Enum b => (a, b) -> Char -> (a, b)
fc' (a
a0, Int
p0) m
c0
      where ft' :: (a, Int) -> m -> (a, Int)
ft' (a
a, Int
p) m
c = ((,) (a -> Int -> (a, Int)) -> a -> Int -> (a, Int)
forall a b. (a -> b) -> a -> b
$! a -> OffsetPositioned m -> a
ft a
a (Int -> m -> OffsetPositioned m
forall m. Int -> m -> OffsetPositioned m
OffsetPositioned Int
p m
c)) (Int -> (a, Int)) -> Int -> (a, Int)
forall a b. (a -> b) -> a -> b
$! Int -> Int
forall a. Enum a => a -> a
succ Int
p
            fc' :: (a, b) -> Char -> (a, b)
fc' (a
a, b
p) Char
c = ((,) (a -> b -> (a, b)) -> a -> b -> (a, b)
forall a b. (a -> b) -> a -> b
$! a -> Char -> a
fc a
a Char
c) (b -> (a, b)) -> b -> (a, b)
forall a b. (a -> b) -> a -> b
$! b -> b
forall a. Enum a => a -> a
succ b
p
   foldr :: (OffsetPositioned m -> a -> a)
-> (Char -> a -> a) -> a -> OffsetPositioned m -> a
foldr OffsetPositioned m -> a -> a
ft Char -> a -> a
fc a
a0 (OffsetPositioned Int
p0 m
c0) = (Int, a) -> a
forall a b. (a, b) -> b
snd ((Int, a) -> a) -> (Int, a) -> a
forall a b. (a -> b) -> a -> b
$ (m -> (Int, a) -> (Int, a))
-> (Char -> (Int, a) -> (Int, a)) -> (Int, a) -> m -> (Int, a)
forall t a.
TextualMonoid t =>
(t -> a -> a) -> (Char -> a -> a) -> a -> t -> a
Textual.foldr m -> (Int, a) -> (Int, a)
ft' Char -> (Int, a) -> (Int, a)
forall a. Enum a => Char -> (a, a) -> (a, a)
fc' (Int
p0, a
a0) m
c0
      where ft' :: m -> (Int, a) -> (Int, a)
ft' m
c (Int
p, a
a) = (Int -> Int
forall a. Enum a => a -> a
succ Int
p, OffsetPositioned m -> a -> a
ft (Int -> m -> OffsetPositioned m
forall m. Int -> m -> OffsetPositioned m
OffsetPositioned Int
p m
c) a
a)
            fc' :: Char -> (a, a) -> (a, a)
fc' Char
c (a
p, a
a) = (a -> a
forall a. Enum a => a -> a
succ a
p, Char -> a -> a
fc Char
c a
a)

   scanl :: (Char -> Char -> Char)
-> Char -> OffsetPositioned m -> OffsetPositioned m
scanl Char -> Char -> Char
f Char
ch (OffsetPositioned Int
p m
c) = Int -> m -> OffsetPositioned m
forall m. Int -> m -> OffsetPositioned m
OffsetPositioned Int
p ((Char -> Char -> Char) -> Char -> m -> m
forall t.
TextualMonoid t =>
(Char -> Char -> Char) -> Char -> t -> t
Textual.scanl Char -> Char -> Char
f Char
ch m
c)
   scanl1 :: (Char -> Char -> Char) -> OffsetPositioned m -> OffsetPositioned m
scanl1 Char -> Char -> Char
f (OffsetPositioned Int
p m
c) = Int -> m -> OffsetPositioned m
forall m. Int -> m -> OffsetPositioned m
OffsetPositioned Int
p ((Char -> Char -> Char) -> m -> m
forall t. TextualMonoid t => (Char -> Char -> Char) -> t -> t
Textual.scanl1 Char -> Char -> Char
f m
c)
   scanr :: (Char -> Char -> Char)
-> Char -> OffsetPositioned m -> OffsetPositioned m
scanr Char -> Char -> Char
f Char
ch (OffsetPositioned Int
p m
c) = Int -> m -> OffsetPositioned m
forall m. Int -> m -> OffsetPositioned m
OffsetPositioned Int
p ((Char -> Char -> Char) -> Char -> m -> m
forall t.
TextualMonoid t =>
(Char -> Char -> Char) -> Char -> t -> t
Textual.scanr Char -> Char -> Char
f Char
ch m
c)
   scanr1 :: (Char -> Char -> Char) -> OffsetPositioned m -> OffsetPositioned m
scanr1 Char -> Char -> Char
f (OffsetPositioned Int
p m
c) = Int -> m -> OffsetPositioned m
forall m. Int -> m -> OffsetPositioned m
OffsetPositioned Int
p ((Char -> Char -> Char) -> m -> m
forall t. TextualMonoid t => (Char -> Char -> Char) -> t -> t
Textual.scanr1 Char -> Char -> Char
f m
c)
   mapAccumL :: (a -> Char -> (a, Char))
-> a -> OffsetPositioned m -> (a, OffsetPositioned m)
mapAccumL a -> Char -> (a, Char)
f a
a0 (OffsetPositioned Int
p m
c) = (m -> OffsetPositioned m) -> (a, m) -> (a, OffsetPositioned m)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Int -> m -> OffsetPositioned m
forall m. Int -> m -> OffsetPositioned m
OffsetPositioned Int
p) ((a -> Char -> (a, Char)) -> a -> m -> (a, m)
forall t a.
TextualMonoid t =>
(a -> Char -> (a, Char)) -> a -> t -> (a, t)
Textual.mapAccumL a -> Char -> (a, Char)
f a
a0 m
c)
   mapAccumR :: (a -> Char -> (a, Char))
-> a -> OffsetPositioned m -> (a, OffsetPositioned m)
mapAccumR a -> Char -> (a, Char)
f a
a0 (OffsetPositioned Int
p m
c) = (m -> OffsetPositioned m) -> (a, m) -> (a, OffsetPositioned m)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Int -> m -> OffsetPositioned m
forall m. Int -> m -> OffsetPositioned m
OffsetPositioned Int
p) ((a -> Char -> (a, Char)) -> a -> m -> (a, m)
forall t a.
TextualMonoid t =>
(a -> Char -> (a, Char)) -> a -> t -> (a, t)
Textual.mapAccumR a -> Char -> (a, Char)
f a
a0 m
c)

   spanMaybe :: s
-> (s -> OffsetPositioned m -> Maybe s)
-> (s -> Char -> Maybe s)
-> OffsetPositioned m
-> (OffsetPositioned m, OffsetPositioned m, s)
spanMaybe s
s0 s -> OffsetPositioned m -> Maybe s
ft s -> Char -> Maybe s
fc (OffsetPositioned Int
p0 m
t) = (m, m, (s, Int)) -> (OffsetPositioned m, OffsetPositioned m, s)
forall m m c.
(m, m, (c, Int)) -> (OffsetPositioned m, OffsetPositioned m, c)
rewrap ((m, m, (s, Int)) -> (OffsetPositioned m, OffsetPositioned m, s))
-> (m, m, (s, Int)) -> (OffsetPositioned m, OffsetPositioned m, s)
forall a b. (a -> b) -> a -> b
$ (s, Int)
-> ((s, Int) -> m -> Maybe (s, Int))
-> ((s, Int) -> Char -> Maybe (s, Int))
-> m
-> (m, m, (s, Int))
forall t s.
TextualMonoid t =>
s
-> (s -> t -> Maybe s) -> (s -> Char -> Maybe s) -> t -> (t, t, s)
Textual.spanMaybe (s
s0, Int
p0) (s, Int) -> m -> Maybe (s, Int)
ft' (s, Int) -> Char -> Maybe (s, Int)
forall b. Enum b => (s, b) -> Char -> Maybe (s, b)
fc' m
t
      where ft' :: (s, Int) -> m -> Maybe (s, Int)
ft' (s
s, Int
p) m
prime = do s
s' <- s -> OffsetPositioned m -> Maybe s
ft s
s (Int -> m -> OffsetPositioned m
forall m. Int -> m -> OffsetPositioned m
OffsetPositioned Int
p m
prime)
                                  let p' :: Int
p' = Int -> Int
forall a. Enum a => a -> a
succ Int
p
                                  (s, Int) -> Maybe (s, Int)
forall a. a -> Maybe a
Just ((s, Int) -> Maybe (s, Int)) -> (s, Int) -> Maybe (s, Int)
forall a b. (a -> b) -> a -> b
$! Int -> (s, Int) -> (s, Int)
seq Int
p' (s
s', Int
p')
            fc' :: (s, b) -> Char -> Maybe (s, b)
fc' (s
s, b
p) Char
c = do s
s' <- s -> Char -> Maybe s
fc s
s Char
c
                              let p' :: b
p' = b -> b
forall a. Enum a => a -> a
succ b
p
                              (s, b) -> Maybe (s, b)
forall a. a -> Maybe a
Just ((s, b) -> Maybe (s, b)) -> (s, b) -> Maybe (s, b)
forall a b. (a -> b) -> a -> b
$! b -> (s, b) -> (s, b)
seq b
p' (s
s', b
p')
            rewrap :: (m, m, (c, Int)) -> (OffsetPositioned m, OffsetPositioned m, c)
rewrap (m
prefix, m
suffix, (c
s, Int
p)) = (Int -> m -> OffsetPositioned m
forall m. Int -> m -> OffsetPositioned m
OffsetPositioned Int
p0 m
prefix, Int -> m -> OffsetPositioned m
forall m. Int -> m -> OffsetPositioned m
OffsetPositioned Int
p m
suffix, c
s)
   spanMaybe' :: s
-> (s -> OffsetPositioned m -> Maybe s)
-> (s -> Char -> Maybe s)
-> OffsetPositioned m
-> (OffsetPositioned m, OffsetPositioned m, s)
spanMaybe' s
s0 s -> OffsetPositioned m -> Maybe s
ft s -> Char -> Maybe s
fc (OffsetPositioned Int
p0 m
t) = (m, m, (s, Int)) -> (OffsetPositioned m, OffsetPositioned m, s)
forall m m c.
(m, m, (c, Int)) -> (OffsetPositioned m, OffsetPositioned m, c)
rewrap ((m, m, (s, Int)) -> (OffsetPositioned m, OffsetPositioned m, s))
-> (m, m, (s, Int)) -> (OffsetPositioned m, OffsetPositioned m, s)
forall a b. (a -> b) -> a -> b
$! (s, Int)
-> ((s, Int) -> m -> Maybe (s, Int))
-> ((s, Int) -> Char -> Maybe (s, Int))
-> m
-> (m, m, (s, Int))
forall t s.
TextualMonoid t =>
s
-> (s -> t -> Maybe s) -> (s -> Char -> Maybe s) -> t -> (t, t, s)
Textual.spanMaybe' (s
s0, Int
p0) (s, Int) -> m -> Maybe (s, Int)
ft' (s, Int) -> Char -> Maybe (s, Int)
forall b. Enum b => (s, b) -> Char -> Maybe (s, b)
fc' m
t
      where ft' :: (s, Int) -> m -> Maybe (s, Int)
ft' (s
s, Int
p) m
prime = do s
s' <- s -> OffsetPositioned m -> Maybe s
ft s
s (Int -> m -> OffsetPositioned m
forall m. Int -> m -> OffsetPositioned m
OffsetPositioned Int
p m
prime)
                                  let p' :: Int
p' = Int -> Int
forall a. Enum a => a -> a
succ Int
p
                                  (s, Int) -> Maybe (s, Int)
forall a. a -> Maybe a
Just ((s, Int) -> Maybe (s, Int)) -> (s, Int) -> Maybe (s, Int)
forall a b. (a -> b) -> a -> b
$! s
s' s -> (s, Int) -> (s, Int)
`seq` Int
p' Int -> (s, Int) -> (s, Int)
`seq` (s
s', Int
p')
            fc' :: (s, b) -> Char -> Maybe (s, b)
fc' (s
s, b
p) Char
c = do s
s' <- s -> Char -> Maybe s
fc s
s Char
c
                              let p' :: b
p' = b -> b
forall a. Enum a => a -> a
succ b
p
                              (s, b) -> Maybe (s, b)
forall a. a -> Maybe a
Just ((s, b) -> Maybe (s, b)) -> (s, b) -> Maybe (s, b)
forall a b. (a -> b) -> a -> b
$! s
s' s -> (s, b) -> (s, b)
`seq` b
p' b -> (s, b) -> (s, b)
`seq` (s
s', b
p')
            rewrap :: (m, m, (c, Int)) -> (OffsetPositioned m, OffsetPositioned m, c)
rewrap (m
prefix, m
suffix, (c
s, Int
p)) = (Int -> m -> OffsetPositioned m
forall m. Int -> m -> OffsetPositioned m
OffsetPositioned Int
p0 m
prefix, Int -> m -> OffsetPositioned m
forall m. Int -> m -> OffsetPositioned m
OffsetPositioned Int
p m
suffix, c
s)
   span :: (OffsetPositioned m -> Bool)
-> (Char -> Bool)
-> OffsetPositioned m
-> (OffsetPositioned m, OffsetPositioned m)
span OffsetPositioned m -> Bool
ft Char -> Bool
fc (OffsetPositioned Int
p0 m
t) = (m, m, Int) -> (OffsetPositioned m, OffsetPositioned m)
forall m m. (m, m, Int) -> (OffsetPositioned m, OffsetPositioned m)
rewrap ((m, m, Int) -> (OffsetPositioned m, OffsetPositioned m))
-> (m, m, Int) -> (OffsetPositioned m, OffsetPositioned m)
forall a b. (a -> b) -> a -> b
$ Int
-> (Int -> m -> Maybe Int)
-> (Int -> Char -> Maybe Int)
-> m
-> (m, m, Int)
forall t s.
TextualMonoid t =>
s
-> (s -> t -> Maybe s) -> (s -> Char -> Maybe s) -> t -> (t, t, s)
Textual.spanMaybe' Int
p0 Int -> m -> Maybe Int
ft' Int -> Char -> Maybe Int
forall a. Enum a => a -> Char -> Maybe a
fc' m
t
      where ft' :: Int -> m -> Maybe Int
ft' Int
p m
prime = if OffsetPositioned m -> Bool
ft (Int -> m -> OffsetPositioned m
forall m. Int -> m -> OffsetPositioned m
OffsetPositioned Int
p m
prime)
                          then Int -> Maybe Int
forall a. a -> Maybe a
Just (Int -> Maybe Int) -> Int -> Maybe Int
forall a b. (a -> b) -> a -> b
$! Int -> Int
forall a. Enum a => a -> a
succ Int
p
                          else Maybe Int
forall a. Maybe a
Nothing
            fc' :: a -> Char -> Maybe a
fc' a
p Char
c = if Char -> Bool
fc Char
c
                      then a -> Maybe a
forall a. a -> Maybe a
Just (a -> Maybe a) -> a -> Maybe a
forall a b. (a -> b) -> a -> b
$! a -> a
forall a. Enum a => a -> a
succ a
p
                      else Maybe a
forall a. Maybe a
Nothing
            rewrap :: (m, m, Int) -> (OffsetPositioned m, OffsetPositioned m)
rewrap (m
prefix, m
suffix, Int
p) = (Int -> m -> OffsetPositioned m
forall m. Int -> m -> OffsetPositioned m
OffsetPositioned Int
p0 m
prefix, Int -> m -> OffsetPositioned m
forall m. Int -> m -> OffsetPositioned m
OffsetPositioned Int
p m
suffix)

   split :: (Char -> Bool) -> OffsetPositioned m -> [OffsetPositioned m]
split Char -> Bool
f (OffsetPositioned Int
p0 m
c0) = Int -> [m] -> [OffsetPositioned m]
forall m. Factorial m => Int -> [m] -> [OffsetPositioned m]
rewrap Int
p0 ((Char -> Bool) -> m -> [m]
forall t. TextualMonoid t => (Char -> Bool) -> t -> [t]
Textual.split Char -> Bool
f m
c0)
      where rewrap :: Int -> [m] -> [OffsetPositioned m]
rewrap Int
_ [] = []
            rewrap Int
p (m
c:[m]
rest) = Int -> m -> OffsetPositioned m
forall m. Int -> m -> OffsetPositioned m
OffsetPositioned Int
p m
c OffsetPositioned m -> [OffsetPositioned m] -> [OffsetPositioned m]
forall a. a -> [a] -> [a]
: Int -> [m] -> [OffsetPositioned m]
rewrap (Int
p Int -> Int -> Int
forall a. Num a => a -> a -> a
+ m -> Int
forall m. Factorial m => m -> Int
length m
c) [m]
rest
   find :: (Char -> Bool) -> OffsetPositioned m -> Maybe Char
find Char -> Bool
p = (Char -> Bool) -> m -> Maybe Char
forall t. TextualMonoid t => (Char -> Bool) -> t -> Maybe Char
find Char -> Bool
p (m -> Maybe Char)
-> (OffsetPositioned m -> m) -> OffsetPositioned m -> Maybe Char
forall b c a. (b -> c) -> (a -> b) -> a -> c
. OffsetPositioned m -> m
forall a. OffsetPositioned a -> a
extractOffset

   foldl_ :: (a -> Char -> a) -> a -> OffsetPositioned m -> a
foldl_ a -> Char -> a
fc a
a0 (OffsetPositioned Int
_ m
c) = (a -> Char -> a) -> a -> m -> a
forall t a. TextualMonoid t => (a -> Char -> a) -> a -> t -> a
Textual.foldl_ a -> Char -> a
fc a
a0 m
c
   foldl_' :: (a -> Char -> a) -> a -> OffsetPositioned m -> a
foldl_' a -> Char -> a
fc a
a0 (OffsetPositioned Int
_ m
c) = (a -> Char -> a) -> a -> m -> a
forall t a. TextualMonoid t => (a -> Char -> a) -> a -> t -> a
Textual.foldl_' a -> Char -> a
fc a
a0 m
c
   foldr_ :: (Char -> a -> a) -> a -> OffsetPositioned m -> a
foldr_ Char -> a -> a
fc a
a0 (OffsetPositioned Int
_ m
c) = (Char -> a -> a) -> a -> m -> a
forall t a. TextualMonoid t => (Char -> a -> a) -> a -> t -> a
Textual.foldr_ Char -> a -> a
fc a
a0 m
c

   spanMaybe_ :: s
-> (s -> Char -> Maybe s)
-> OffsetPositioned m
-> (OffsetPositioned m, OffsetPositioned m, s)
spanMaybe_ s
s0 s -> Char -> Maybe s
fc (OffsetPositioned Int
p0 m
t) = (m, m, (s, Int)) -> (OffsetPositioned m, OffsetPositioned m, s)
forall m m c.
(m, m, (c, Int)) -> (OffsetPositioned m, OffsetPositioned m, c)
rewrap ((m, m, (s, Int)) -> (OffsetPositioned m, OffsetPositioned m, s))
-> (m, m, (s, Int)) -> (OffsetPositioned m, OffsetPositioned m, s)
forall a b. (a -> b) -> a -> b
$ (s, Int)
-> ((s, Int) -> Char -> Maybe (s, Int)) -> m -> (m, m, (s, Int))
forall t s.
TextualMonoid t =>
s -> (s -> Char -> Maybe s) -> t -> (t, t, s)
Textual.spanMaybe_' (s
s0, Int
p0) (s, Int) -> Char -> Maybe (s, Int)
forall b. Enum b => (s, b) -> Char -> Maybe (s, b)
fc' m
t
      where fc' :: (s, b) -> Char -> Maybe (s, b)
fc' (s
s, b
p) Char
c = do s
s' <- s -> Char -> Maybe s
fc s
s Char
c
                              let p' :: b
p' = b -> b
forall a. Enum a => a -> a
succ b
p
                              (s, b) -> Maybe (s, b)
forall a. a -> Maybe a
Just ((s, b) -> Maybe (s, b)) -> (s, b) -> Maybe (s, b)
forall a b. (a -> b) -> a -> b
$! b -> (s, b) -> (s, b)
seq b
p' (s
s', b
p')
            rewrap :: (m, m, (c, Int)) -> (OffsetPositioned m, OffsetPositioned m, c)
rewrap (m
prefix, m
suffix, (c
s, Int
p)) = (Int -> m -> OffsetPositioned m
forall m. Int -> m -> OffsetPositioned m
OffsetPositioned Int
p0 m
prefix, Int -> m -> OffsetPositioned m
forall m. Int -> m -> OffsetPositioned m
OffsetPositioned Int
p m
suffix, c
s)
   spanMaybe_' :: s
-> (s -> Char -> Maybe s)
-> OffsetPositioned m
-> (OffsetPositioned m, OffsetPositioned m, s)
spanMaybe_' s
s0 s -> Char -> Maybe s
fc (OffsetPositioned Int
p0 m
t) = (m, m, (s, Int)) -> (OffsetPositioned m, OffsetPositioned m, s)
forall m m c.
(m, m, (c, Int)) -> (OffsetPositioned m, OffsetPositioned m, c)
rewrap ((m, m, (s, Int)) -> (OffsetPositioned m, OffsetPositioned m, s))
-> (m, m, (s, Int)) -> (OffsetPositioned m, OffsetPositioned m, s)
forall a b. (a -> b) -> a -> b
$! (s, Int)
-> ((s, Int) -> Char -> Maybe (s, Int)) -> m -> (m, m, (s, Int))
forall t s.
TextualMonoid t =>
s -> (s -> Char -> Maybe s) -> t -> (t, t, s)
Textual.spanMaybe_' (s
s0, Int
p0) (s, Int) -> Char -> Maybe (s, Int)
forall b. Enum b => (s, b) -> Char -> Maybe (s, b)
fc' m
t
      where fc' :: (s, b) -> Char -> Maybe (s, b)
fc' (s
s, b
p) Char
c = do s
s' <- s -> Char -> Maybe s
fc s
s Char
c
                              let p' :: b
p' = b -> b
forall a. Enum a => a -> a
succ b
p
                              (s, b) -> Maybe (s, b)
forall a. a -> Maybe a
Just ((s, b) -> Maybe (s, b)) -> (s, b) -> Maybe (s, b)
forall a b. (a -> b) -> a -> b
$! s
s' s -> (s, b) -> (s, b)
`seq` b
p' b -> (s, b) -> (s, b)
`seq` (s
s', b
p')
            rewrap :: (m, m, (c, Int)) -> (OffsetPositioned m, OffsetPositioned m, c)
rewrap (m
prefix, m
suffix, (c
s, Int
p)) = (Int -> m -> OffsetPositioned m
forall m. Int -> m -> OffsetPositioned m
OffsetPositioned Int
p0 m
prefix, Int -> m -> OffsetPositioned m
forall m. Int -> m -> OffsetPositioned m
OffsetPositioned Int
p m
suffix, c
s)
   span_ :: Bool
-> (Char -> Bool)
-> OffsetPositioned m
-> (OffsetPositioned m, OffsetPositioned m)
span_ Bool
bt Char -> Bool
fc (OffsetPositioned Int
p0 m
t) = (m, m) -> (OffsetPositioned m, OffsetPositioned m)
forall m m.
Factorial m =>
(m, m) -> (OffsetPositioned m, OffsetPositioned m)
rewrap ((m, m) -> (OffsetPositioned m, OffsetPositioned m))
-> (m, m) -> (OffsetPositioned m, OffsetPositioned m)
forall a b. (a -> b) -> a -> b
$ Bool -> (Char -> Bool) -> m -> (m, m)
forall t. TextualMonoid t => Bool -> (Char -> Bool) -> t -> (t, t)
Textual.span_ Bool
bt Char -> Bool
fc m
t
      where rewrap :: (m, m) -> (OffsetPositioned m, OffsetPositioned m)
rewrap (m
prefix, m
suffix) = (Int -> m -> OffsetPositioned m
forall m. Int -> m -> OffsetPositioned m
OffsetPositioned Int
p0 m
prefix, Int -> m -> OffsetPositioned m
forall m. Int -> m -> OffsetPositioned m
OffsetPositioned (Int
p0 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ m -> Int
forall m. Factorial m => m -> Int
length m
prefix) m
suffix)
   break_ :: Bool
-> (Char -> Bool)
-> OffsetPositioned m
-> (OffsetPositioned m, OffsetPositioned m)
break_ Bool
bt Char -> Bool
fc (OffsetPositioned Int
p0 m
t) = (m, m) -> (OffsetPositioned m, OffsetPositioned m)
forall m m.
Factorial m =>
(m, m) -> (OffsetPositioned m, OffsetPositioned m)
rewrap ((m, m) -> (OffsetPositioned m, OffsetPositioned m))
-> (m, m) -> (OffsetPositioned m, OffsetPositioned m)
forall a b. (a -> b) -> a -> b
$ Bool -> (Char -> Bool) -> m -> (m, m)
forall t. TextualMonoid t => Bool -> (Char -> Bool) -> t -> (t, t)
Textual.break_ Bool
bt Char -> Bool
fc m
t
      where rewrap :: (m, m) -> (OffsetPositioned m, OffsetPositioned m)
rewrap (m
prefix, m
suffix) = (Int -> m -> OffsetPositioned m
forall m. Int -> m -> OffsetPositioned m
OffsetPositioned Int
p0 m
prefix, Int -> m -> OffsetPositioned m
forall m. Int -> m -> OffsetPositioned m
OffsetPositioned (Int
p0 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ m -> Int
forall m. Factorial m => m -> Int
length m
prefix) m
suffix)
   dropWhile_ :: Bool -> (Char -> Bool) -> OffsetPositioned m -> OffsetPositioned m
dropWhile_ Bool
bt Char -> Bool
fc OffsetPositioned m
t = (OffsetPositioned m, OffsetPositioned m) -> OffsetPositioned m
forall a b. (a, b) -> b
snd (Bool
-> (Char -> Bool)
-> OffsetPositioned m
-> (OffsetPositioned m, OffsetPositioned m)
forall t. TextualMonoid t => Bool -> (Char -> Bool) -> t -> (t, t)
span_ Bool
bt Char -> Bool
fc OffsetPositioned m
t)
   takeWhile_ :: Bool -> (Char -> Bool) -> OffsetPositioned m -> OffsetPositioned m
takeWhile_ Bool
bt Char -> Bool
fc (OffsetPositioned Int
p m
t) = Int -> m -> OffsetPositioned m
forall m. Int -> m -> OffsetPositioned m
OffsetPositioned Int
p (Bool -> (Char -> Bool) -> m -> m
forall t. TextualMonoid t => Bool -> (Char -> Bool) -> t -> t
takeWhile_ Bool
bt Char -> Bool
fc m
t)
   toString :: (OffsetPositioned m -> String) -> OffsetPositioned m -> String
toString OffsetPositioned m -> String
ft (OffsetPositioned Int
_ m
t) = (m -> String) -> m -> String
forall t. TextualMonoid t => (t -> String) -> t -> String
toString (OffsetPositioned m -> String
ft (OffsetPositioned m -> String)
-> (m -> OffsetPositioned m) -> m -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. m -> OffsetPositioned m
forall (f :: * -> *) a. Applicative f => a -> f a
pure) m
t
   toText :: (OffsetPositioned m -> Text) -> OffsetPositioned m -> Text
toText OffsetPositioned m -> Text
ft (OffsetPositioned Int
_ m
t) = (m -> Text) -> m -> Text
forall t. TextualMonoid t => (t -> Text) -> t -> Text
toText (OffsetPositioned m -> Text
ft (OffsetPositioned m -> Text)
-> (m -> OffsetPositioned m) -> m -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. m -> OffsetPositioned m
forall (f :: * -> *) a. Applicative f => a -> f a
pure) m
t

   {-# INLINE characterPrefix #-}
   {-# INLINE splitCharacterPrefix #-}
   {-# INLINE map #-}
   {-# INLINE concatMap #-}
   {-# INLINE foldl' #-}
   {-# INLINE foldr #-}
   {-# INLINE spanMaybe' #-}
   {-# INLINE span #-}
   {-# INLINE foldl_' #-}
   {-# INLINE foldr_ #-}
   {-# INLINE any #-}
   {-# INLINE all #-}
   {-# INLINE spanMaybe_' #-}
   {-# INLINE span_ #-}
   {-# INLINE break_ #-}
   {-# INLINE dropWhile_ #-}
   {-# INLINE takeWhile_ #-}
   {-# INLINE split #-}
   {-# INLINE find #-}

instance (StableFactorial m, TextualMonoid m) => TextualMonoid (LinePositioned m) where
   splitCharacterPrefix :: LinePositioned m -> Maybe (Char, LinePositioned m)
splitCharacterPrefix (LinePositioned Int
p Int
l Int
lp m
t) =
      case m -> Maybe (Char, m)
forall t. TextualMonoid t => t -> Maybe (Char, t)
splitCharacterPrefix m
t
      of Maybe (Char, m)
Nothing -> Maybe (Char, LinePositioned m)
forall a. Maybe a
Nothing
         Just (Char
c, m
rest) | m -> Bool
forall m. MonoidNull m => m -> Bool
null m
rest -> (Char, LinePositioned m) -> Maybe (Char, LinePositioned m)
forall a. a -> Maybe a
Just (Char
c, LinePositioned m
forall a. Monoid a => a
mempty)
         Just (Char
'\n', m
rest) -> (Char, LinePositioned m) -> Maybe (Char, LinePositioned m)
forall a. a -> Maybe a
Just (Char
'\n', Int -> Int -> Int -> m -> LinePositioned m
forall m. Int -> Int -> Int -> m -> LinePositioned m
LinePositioned Int
p' (Int -> Int
forall a. Enum a => a -> a
succ Int
l) Int
p m
rest)
         Just (Char
'\f', m
rest) -> (Char, LinePositioned m) -> Maybe (Char, LinePositioned m)
forall a. a -> Maybe a
Just (Char
'\f', Int -> Int -> Int -> m -> LinePositioned m
forall m. Int -> Int -> Int -> m -> LinePositioned m
LinePositioned Int
p' (Int -> Int
forall a. Enum a => a -> a
succ Int
l) Int
p m
rest)
         Just (Char
'\r', m
rest) -> (Char, LinePositioned m) -> Maybe (Char, LinePositioned m)
forall a. a -> Maybe a
Just (Char
'\r', Int -> Int -> Int -> m -> LinePositioned m
forall m. Int -> Int -> Int -> m -> LinePositioned m
LinePositioned Int
p' Int
l Int
p m
rest)
         Just (Char
'\t', m
rest) -> (Char, LinePositioned m) -> Maybe (Char, LinePositioned m)
forall a. a -> Maybe a
Just (Char
'\t', Int -> Int -> Int -> m -> LinePositioned m
forall m. Int -> Int -> Int -> m -> LinePositioned m
LinePositioned Int
p' Int
l (Int
lp Int -> Int -> Int
forall a. Num a => a -> a -> a
+ (Int
p Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
lp) Int -> Int -> Int
forall a. Integral a => a -> a -> a
`mod` Int
8 Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
8) m
rest)
         Just (Char
ch, m
rest) -> (Char, LinePositioned m) -> Maybe (Char, LinePositioned m)
forall a. a -> Maybe a
Just (Char
ch, Int -> Int -> Int -> m -> LinePositioned m
forall m. Int -> Int -> Int -> m -> LinePositioned m
LinePositioned Int
p' Int
l Int
lp m
rest)
      where p' :: Int
p' = Int -> Int
forall a. Enum a => a -> a
succ Int
p

   fromText :: Text -> LinePositioned m
fromText = m -> LinePositioned m
forall (f :: * -> *) a. Applicative f => a -> f a
pure (m -> LinePositioned m) -> (Text -> m) -> Text -> LinePositioned m
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> m
forall t. TextualMonoid t => Text -> t
fromText
   singleton :: Char -> LinePositioned m
singleton = m -> LinePositioned m
forall (f :: * -> *) a. Applicative f => a -> f a
pure (m -> LinePositioned m) -> (Char -> m) -> Char -> LinePositioned m
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> m
forall t. TextualMonoid t => Char -> t
singleton

   characterPrefix :: LinePositioned m -> Maybe Char
characterPrefix = m -> Maybe Char
forall t. TextualMonoid t => t -> Maybe Char
characterPrefix (m -> Maybe Char)
-> (LinePositioned m -> m) -> LinePositioned m -> Maybe Char
forall b c a. (b -> c) -> (a -> b) -> a -> c
. LinePositioned m -> m
forall a. LinePositioned a -> a
extractLines

   map :: (Char -> Char) -> LinePositioned m -> LinePositioned m
map Char -> Char
f (LinePositioned Int
p Int
l Int
lp m
c) = Int -> Int -> Int -> m -> LinePositioned m
forall m. Int -> Int -> Int -> m -> LinePositioned m
LinePositioned Int
p Int
l Int
lp ((Char -> Char) -> m -> m
forall t. TextualMonoid t => (Char -> Char) -> t -> t
map Char -> Char
f m
c)
   concatMap :: (Char -> LinePositioned m) -> LinePositioned m -> LinePositioned m
concatMap Char -> LinePositioned m
f (LinePositioned Int
p Int
l Int
lp m
c) = Int -> Int -> Int -> m -> LinePositioned m
forall m. Int -> Int -> Int -> m -> LinePositioned m
LinePositioned Int
p Int
l Int
lp ((Char -> m) -> m -> m
forall t. TextualMonoid t => (Char -> t) -> t -> t
concatMap (LinePositioned m -> m
forall a. LinePositioned a -> a
extractLines (LinePositioned m -> m) -> (Char -> LinePositioned m) -> Char -> m
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> LinePositioned m
f) m
c)
   all :: (Char -> Bool) -> LinePositioned m -> Bool
all Char -> Bool
p = (Char -> Bool) -> m -> Bool
forall t. TextualMonoid t => (Char -> Bool) -> t -> Bool
all Char -> Bool
p (m -> Bool) -> (LinePositioned m -> m) -> LinePositioned m -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. LinePositioned m -> m
forall a. LinePositioned a -> a
extractLines
   any :: (Char -> Bool) -> LinePositioned m -> Bool
any Char -> Bool
p = (Char -> Bool) -> m -> Bool
forall t. TextualMonoid t => (Char -> Bool) -> t -> Bool
any Char -> Bool
p (m -> Bool) -> (LinePositioned m -> m) -> LinePositioned m -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. LinePositioned m -> m
forall a. LinePositioned a -> a
extractLines

   foldl :: (a -> LinePositioned m -> a)
-> (a -> Char -> a) -> a -> LinePositioned m -> a
foldl a -> LinePositioned m -> a
ft a -> Char -> a
fc a
a0 (LinePositioned Int
p0 Int
l0 Int
lp0 m
c0) = (a, Int, Int, Int) -> a
forall a b c d. (a, b, c, d) -> a
fstOf4 ((a, Int, Int, Int) -> a) -> (a, Int, Int, Int) -> a
forall a b. (a -> b) -> a -> b
$ ((a, Int, Int, Int) -> m -> (a, Int, Int, Int))
-> ((a, Int, Int, Int) -> Char -> (a, Int, Int, Int))
-> (a, Int, Int, Int)
-> m
-> (a, Int, Int, Int)
forall t a.
TextualMonoid t =>
(a -> t -> a) -> (a -> Char -> a) -> a -> t -> a
Textual.foldl (a, Int, Int, Int) -> m -> (a, Int, Int, Int)
ft' (a, Int, Int, Int) -> Char -> (a, Int, Int, Int)
forall a a.
(Enum a, Integral a) =>
(a, a, a, a) -> Char -> (a, a, a, a)
fc' (a
a0, Int
p0, Int
l0, Int
lp0) m
c0
      where ft' :: (a, Int, Int, Int) -> m -> (a, Int, Int, Int)
ft' (a
a, Int
p, Int
l, Int
lp) m
c = (a -> LinePositioned m -> a
ft a
a (Int -> Int -> Int -> m -> LinePositioned m
forall m. Int -> Int -> Int -> m -> LinePositioned m
LinePositioned Int
p Int
l Int
lp m
c), Int -> Int
forall a. Enum a => a -> a
succ Int
p, Int
l, Int
lp)
            fc' :: (a, a, a, a) -> Char -> (a, a, a, a)
fc' (a
a, a
p, a
l, a
_lp) Char
'\n' = (a -> Char -> a
fc a
a Char
'\n', a -> a
forall a. Enum a => a -> a
succ a
p, a -> a
forall a. Enum a => a -> a
succ a
l, a
p)
            fc' (a
a, a
p, a
l, a
_lp) Char
'\f' = (a -> Char -> a
fc a
a Char
'\f', a -> a
forall a. Enum a => a -> a
succ a
p, a -> a
forall a. Enum a => a -> a
succ a
l, a
p)
            fc' (a
a, a
p, a
l, a
_lp) Char
'\r' = (a -> Char -> a
fc a
a Char
'\r', a -> a
forall a. Enum a => a -> a
succ a
p, a
l, a
p)
            fc' (a
a, a
p, a
l, a
lp) Char
'\t' = (a -> Char -> a
fc a
a Char
'\t', a -> a
forall a. Enum a => a -> a
succ a
p, a
l, a
lp a -> a -> a
forall a. Num a => a -> a -> a
+ (a
p a -> a -> a
forall a. Num a => a -> a -> a
- a
lp) a -> a -> a
forall a. Integral a => a -> a -> a
`mod` a
8 a -> a -> a
forall a. Num a => a -> a -> a
- a
8)
            fc' (a
a, a
p, a
l, a
lp) Char
c = (a -> Char -> a
fc a
a Char
c, a -> a
forall a. Enum a => a -> a
succ a
p, a
l, a
lp)
   foldl' :: (a -> LinePositioned m -> a)
-> (a -> Char -> a) -> a -> LinePositioned m -> a
foldl' a -> LinePositioned m -> a
ft a -> Char -> a
fc a
a0 (LinePositioned Int
p0 Int
l0 Int
lp0 m
c0) = (a, Int, Int, Int) -> a
forall a b c d. (a, b, c, d) -> a
fstOf4 ((a, Int, Int, Int) -> a) -> (a, Int, Int, Int) -> a
forall a b. (a -> b) -> a -> b
$ ((a, Int, Int, Int) -> m -> (a, Int, Int, Int))
-> ((a, Int, Int, Int) -> Char -> (a, Int, Int, Int))
-> (a, Int, Int, Int)
-> m
-> (a, Int, Int, Int)
forall t a.
TextualMonoid t =>
(a -> t -> a) -> (a -> Char -> a) -> a -> t -> a
Textual.foldl' (a, Int, Int, Int) -> m -> (a, Int, Int, Int)
ft' (a, Int, Int, Int) -> Char -> (a, Int, Int, Int)
forall a c.
(Integral a, Enum c) =>
(a, a, c, a) -> Char -> (a, a, c, a)
fc' (a
a0, Int
p0, Int
l0, Int
lp0) m
c0
      where ft' :: (a, Int, Int, Int) -> m -> (a, Int, Int, Int)
ft' (a
a, Int
p, Int
l, Int
lp) m
c = let a' :: a
a' = a -> LinePositioned m -> a
ft a
a (Int -> Int -> Int -> m -> LinePositioned m
forall m. Int -> Int -> Int -> m -> LinePositioned m
LinePositioned Int
p Int
l Int
lp m
c)
                                      p' :: Int
p' = Int -> Int
forall a. Enum a => a -> a
succ Int
p
                                  in a
a' a -> (a, Int, Int, Int) -> (a, Int, Int, Int)
`seq` Int
p' Int -> (a, Int, Int, Int) -> (a, Int, Int, Int)
`seq` (a
a', Int
p', Int
l, Int
lp)
            fc' :: (a, a, c, a) -> Char -> (a, a, c, a)
fc' (a
a, a
p, c
l, a
lp) Char
c = let a' :: a
a' = a -> Char -> a
fc a
a Char
c
                                      p' :: a
p' = a -> a
forall a. Enum a => a -> a
succ a
p
                                      l' :: c
l' = c -> c
forall a. Enum a => a -> a
succ c
l
                                  in a
a' a -> (a, a, c, a) -> (a, a, c, a)
`seq` a
p' a -> (a, a, c, a) -> (a, a, c, a)
`seq` case Char
c
                                                       of Char
'\n' -> c
l' c -> (a, a, c, a) -> (a, a, c, a)
`seq` (a
a', a
p', c
l', a
p)
                                                          Char
'\f' -> c
l' c -> (a, a, c, a) -> (a, a, c, a)
`seq` (a
a', a
p', c
l', a
p)
                                                          Char
'\r' -> (a
a', a
p', c
l, a
p)
                                                          Char
'\t' -> (a
a', a
p', c
l, a
lp a -> a -> a
forall a. Num a => a -> a -> a
+ (a
p a -> a -> a
forall a. Num a => a -> a -> a
- a
lp) a -> a -> a
forall a. Integral a => a -> a -> a
`mod` a
8 a -> a -> a
forall a. Num a => a -> a -> a
- a
8)
                                                          Char
_ -> (a
a', a
p', c
l, a
lp)
   foldr :: (LinePositioned m -> a -> a)
-> (Char -> a -> a) -> a -> LinePositioned m -> a
foldr LinePositioned m -> a -> a
ft Char -> a -> a
fc a
a0 (LinePositioned Int
p0 Int
l0 Int
lp0 m
c0) = (m -> (Int -> Int -> Int -> a) -> Int -> Int -> Int -> a)
-> (Char -> (Int -> Int -> Int -> a) -> Int -> Int -> Int -> a)
-> (Int -> Int -> Int -> a)
-> m
-> Int
-> Int
-> Int
-> a
forall t a.
TextualMonoid t =>
(t -> a -> a) -> (Char -> a -> a) -> a -> t -> a
Textual.foldr m -> (Int -> Int -> Int -> a) -> Int -> Int -> Int -> a
ft' Char -> (Int -> Int -> Int -> a) -> Int -> Int -> Int -> a
forall a a.
(Enum a, Integral a) =>
Char -> (a -> a -> a -> a) -> a -> a -> a -> a
fc' (a -> Int -> Int -> Int -> a
forall a b c d. a -> b -> c -> d -> a
const3 a
a0) m
c0 Int
p0 Int
l0 Int
lp0
      where ft' :: m -> (Int -> Int -> Int -> a) -> Int -> Int -> Int -> a
ft' m
c Int -> Int -> Int -> a
cont Int
p Int
l Int
lp = LinePositioned m -> a -> a
ft (Int -> Int -> Int -> m -> LinePositioned m
forall m. Int -> Int -> Int -> m -> LinePositioned m
LinePositioned Int
p Int
l Int
lp m
c) (a -> a) -> a -> a
forall a b. (a -> b) -> a -> b
$ (Int -> Int -> Int -> a
cont (Int -> Int -> Int -> a) -> Int -> Int -> Int -> a
forall a b. (a -> b) -> a -> b
$! Int -> Int
forall a. Enum a => a -> a
succ Int
p) Int
l Int
lp
            fc' :: Char -> (a -> a -> a -> a) -> a -> a -> a -> a
fc' Char
c a -> a -> a -> a
cont a
p a
l a
lp
               | Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'\n' = Char -> a -> a
fc Char
c (a -> a) -> a -> a
forall a b. (a -> b) -> a -> b
$ ((a -> a -> a -> a
cont (a -> a -> a -> a) -> a -> a -> a -> a
forall a b. (a -> b) -> a -> b
$! a -> a
forall a. Enum a => a -> a
succ a
p) (a -> a -> a) -> a -> a -> a
forall a b. (a -> b) -> a -> b
$! a -> a
forall a. Enum a => a -> a
succ a
l) a
p
               | Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'\f' = Char -> a -> a
fc Char
c (a -> a) -> a -> a
forall a b. (a -> b) -> a -> b
$ ((a -> a -> a -> a
cont (a -> a -> a -> a) -> a -> a -> a -> a
forall a b. (a -> b) -> a -> b
$! a -> a
forall a. Enum a => a -> a
succ a
p) (a -> a -> a) -> a -> a -> a
forall a b. (a -> b) -> a -> b
$! a -> a
forall a. Enum a => a -> a
succ a
l) a
p
               | Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'\r' = Char -> a -> a
fc Char
c (a -> a) -> a -> a
forall a b. (a -> b) -> a -> b
$ (a -> a -> a -> a
cont (a -> a -> a -> a) -> a -> a -> a -> a
forall a b. (a -> b) -> a -> b
$! a -> a
forall a. Enum a => a -> a
succ a
p) a
l a
p
               | Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'\t' = Char -> a -> a
fc Char
c (a -> a) -> a -> a
forall a b. (a -> b) -> a -> b
$ (a -> a -> a -> a
cont (a -> a -> a -> a) -> a -> a -> a -> a
forall a b. (a -> b) -> a -> b
$! a -> a
forall a. Enum a => a -> a
succ a
p) a
l (a
lp a -> a -> a
forall a. Num a => a -> a -> a
+ (a
p a -> a -> a
forall a. Num a => a -> a -> a
- a
lp) a -> a -> a
forall a. Integral a => a -> a -> a
`mod` a
8 a -> a -> a
forall a. Num a => a -> a -> a
- a
8)
               | Bool
otherwise = Char -> a -> a
fc Char
c (a -> a) -> a -> a
forall a b. (a -> b) -> a -> b
$ (a -> a -> a -> a
cont (a -> a -> a -> a) -> a -> a -> a -> a
forall a b. (a -> b) -> a -> b
$! a -> a
forall a. Enum a => a -> a
succ a
p) a
l a
lp

   spanMaybe :: s
-> (s -> LinePositioned m -> Maybe s)
-> (s -> Char -> Maybe s)
-> LinePositioned m
-> (LinePositioned m, LinePositioned m, s)
spanMaybe s
s0 s -> LinePositioned m -> Maybe s
ft s -> Char -> Maybe s
fc (LinePositioned Int
p0 Int
l0 Int
lp0 m
t) = (m, m, (s, Int, Int, Int))
-> (LinePositioned m, LinePositioned m, s)
forall m m c.
(m, m, (c, Int, Int, Int))
-> (LinePositioned m, LinePositioned m, c)
rewrap ((m, m, (s, Int, Int, Int))
 -> (LinePositioned m, LinePositioned m, s))
-> (m, m, (s, Int, Int, Int))
-> (LinePositioned m, LinePositioned m, s)
forall a b. (a -> b) -> a -> b
$ (s, Int, Int, Int)
-> ((s, Int, Int, Int) -> m -> Maybe (s, Int, Int, Int))
-> ((s, Int, Int, Int) -> Char -> Maybe (s, Int, Int, Int))
-> m
-> (m, m, (s, Int, Int, Int))
forall t s.
TextualMonoid t =>
s
-> (s -> t -> Maybe s) -> (s -> Char -> Maybe s) -> t -> (t, t, s)
Textual.spanMaybe (s
s0, Int
p0, Int
l0, Int
lp0) (s, Int, Int, Int) -> m -> Maybe (s, Int, Int, Int)
ft' (s, Int, Int, Int) -> Char -> Maybe (s, Int, Int, Int)
forall a c.
(Integral a, Enum c) =>
(s, a, c, a) -> Char -> Maybe (s, a, c, a)
fc' m
t
      where ft' :: (s, Int, Int, Int) -> m -> Maybe (s, Int, Int, Int)
ft' (s
s, Int
p, Int
l, Int
lp) m
prime = do s
s' <- s -> LinePositioned m -> Maybe s
ft s
s (Int -> Int -> Int -> m -> LinePositioned m
forall m. Int -> Int -> Int -> m -> LinePositioned m
LinePositioned Int
p Int
l Int
lp m
prime)
                                         let p' :: Int
p' = Int -> Int
forall a. Enum a => a -> a
succ Int
p
                                         (s, Int, Int, Int) -> Maybe (s, Int, Int, Int)
forall a. a -> Maybe a
Just ((s, Int, Int, Int) -> Maybe (s, Int, Int, Int))
-> (s, Int, Int, Int) -> Maybe (s, Int, Int, Int)
forall a b. (a -> b) -> a -> b
$! Int -> (s, Int, Int, Int) -> (s, Int, Int, Int)
seq Int
p' (s
s', Int
p', Int
l, Int
lp)
            fc' :: (s, a, c, a) -> Char -> Maybe (s, a, c, a)
fc' (s
s, a
p, c
l, a
lp) Char
c = s -> Char -> Maybe s
fc s
s Char
c
                                  Maybe s -> (s -> Maybe (s, a, c, a)) -> Maybe (s, a, c, a)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \s
s'-> (s, a, c, a) -> Maybe (s, a, c, a)
forall a. a -> Maybe a
Just ((s, a, c, a) -> Maybe (s, a, c, a))
-> (s, a, c, a) -> Maybe (s, a, c, a)
forall a b. (a -> b) -> a -> b
$! a -> (s, a, c, a) -> (s, a, c, a)
seq a
p' (if Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'\n' Bool -> Bool -> Bool
|| Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'\f' then c -> (s, a, c, a) -> (s, a, c, a)
seq c
l' (s
s', a
p', c
l', a
p)
                                                            else if Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'\r' then (s
s', a
p', c
l, a
p)
                                                            else if Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'\t' then (s
s', a
p', c
l, a
lp a -> a -> a
forall a. Num a => a -> a -> a
+ (a
p a -> a -> a
forall a. Num a => a -> a -> a
- a
lp) a -> a -> a
forall a. Integral a => a -> a -> a
`mod` a
8 a -> a -> a
forall a. Num a => a -> a -> a
- a
8)
                                                            else (s
s', a
p', c
l, a
lp))
               where p' :: a
p' = a -> a
forall a. Enum a => a -> a
succ a
p
                     l' :: c
l' = c -> c
forall a. Enum a => a -> a
succ c
l
            rewrap :: (m, m, (c, Int, Int, Int))
-> (LinePositioned m, LinePositioned m, c)
rewrap (m
prefix, m
suffix, (c
s, Int
p, Int
l, Int
lp)) = (Int -> Int -> Int -> m -> LinePositioned m
forall m. Int -> Int -> Int -> m -> LinePositioned m
LinePositioned Int
p0 Int
l0 Int
lp0 m
prefix, Int -> Int -> Int -> m -> LinePositioned m
forall m. Int -> Int -> Int -> m -> LinePositioned m
LinePositioned Int
p Int
l Int
lp m
suffix, c
s)
   spanMaybe' :: s
-> (s -> LinePositioned m -> Maybe s)
-> (s -> Char -> Maybe s)
-> LinePositioned m
-> (LinePositioned m, LinePositioned m, s)
spanMaybe' s
s0 s -> LinePositioned m -> Maybe s
ft s -> Char -> Maybe s
fc (LinePositioned Int
p0 Int
l0 Int
lp0 m
t) = (m, m, (s, Int, Int, Int))
-> (LinePositioned m, LinePositioned m, s)
forall m m c.
(m, m, (c, Int, Int, Int))
-> (LinePositioned m, LinePositioned m, c)
rewrap ((m, m, (s, Int, Int, Int))
 -> (LinePositioned m, LinePositioned m, s))
-> (m, m, (s, Int, Int, Int))
-> (LinePositioned m, LinePositioned m, s)
forall a b. (a -> b) -> a -> b
$! (s, Int, Int, Int)
-> ((s, Int, Int, Int) -> m -> Maybe (s, Int, Int, Int))
-> ((s, Int, Int, Int) -> Char -> Maybe (s, Int, Int, Int))
-> m
-> (m, m, (s, Int, Int, Int))
forall t s.
TextualMonoid t =>
s
-> (s -> t -> Maybe s) -> (s -> Char -> Maybe s) -> t -> (t, t, s)
Textual.spanMaybe' (s
s0, Int
p0, Int
l0, Int
lp0) (s, Int, Int, Int) -> m -> Maybe (s, Int, Int, Int)
ft' (s, Int, Int, Int) -> Char -> Maybe (s, Int, Int, Int)
forall a c.
(Integral a, Enum c) =>
(s, a, c, a) -> Char -> Maybe (s, a, c, a)
fc' m
t
      where ft' :: (s, Int, Int, Int) -> m -> Maybe (s, Int, Int, Int)
ft' (s
s, Int
p, Int
l, Int
lp) m
prime = do s
s' <- s -> LinePositioned m -> Maybe s
ft s
s (Int -> Int -> Int -> m -> LinePositioned m
forall m. Int -> Int -> Int -> m -> LinePositioned m
LinePositioned Int
p Int
l Int
lp m
prime)
                                         let p' :: Int
p' = Int -> Int
forall a. Enum a => a -> a
succ Int
p
                                         (s, Int, Int, Int) -> Maybe (s, Int, Int, Int)
forall a. a -> Maybe a
Just ((s, Int, Int, Int) -> Maybe (s, Int, Int, Int))
-> (s, Int, Int, Int) -> Maybe (s, Int, Int, Int)
forall a b. (a -> b) -> a -> b
$! s
s' s -> (s, Int, Int, Int) -> (s, Int, Int, Int)
`seq` Int
p' Int -> (s, Int, Int, Int) -> (s, Int, Int, Int)
`seq` (s
s', Int
p', Int
l, Int
lp)
            fc' :: (s, a, c, a) -> Char -> Maybe (s, a, c, a)
fc' (s
s, a
p, c
l, a
lp) Char
c = do s
s' <- s -> Char -> Maybe s
fc s
s Char
c
                                     let p' :: a
p' = a -> a
forall a. Enum a => a -> a
succ a
p
                                         l' :: c
l' = c -> c
forall a. Enum a => a -> a
succ c
l
                                     (s, a, c, a) -> Maybe (s, a, c, a)
forall a. a -> Maybe a
Just ((s, a, c, a) -> Maybe (s, a, c, a))
-> (s, a, c, a) -> Maybe (s, a, c, a)
forall a b. (a -> b) -> a -> b
$! s
s' s -> (s, a, c, a) -> (s, a, c, a)
`seq` a
p' a -> (s, a, c, a) -> (s, a, c, a)
`seq` (if Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'\n' Bool -> Bool -> Bool
|| Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'\f' then c -> (s, a, c, a) -> (s, a, c, a)
seq c
l' (s
s', a
p', c
l', a
p)
                                                                else if Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'\r' then (s
s', a
p', c
l, a
p)
                                                                else if Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'\t' then (s
s', a
p', c
l, a
lp a -> a -> a
forall a. Num a => a -> a -> a
+ (a
p a -> a -> a
forall a. Num a => a -> a -> a
- a
lp) a -> a -> a
forall a. Integral a => a -> a -> a
`mod` a
8 a -> a -> a
forall a. Num a => a -> a -> a
- a
8)
                                                                else (s
s', a
p', c
l, a
lp))
            rewrap :: (m, m, (c, Int, Int, Int))
-> (LinePositioned m, LinePositioned m, c)
rewrap (m
prefix, m
suffix, (c
s, Int
p, Int
l, Int
lp)) = (Int -> Int -> Int -> m -> LinePositioned m
forall m. Int -> Int -> Int -> m -> LinePositioned m
LinePositioned Int
p0 Int
l0 Int
lp0 m
prefix, Int -> Int -> Int -> m -> LinePositioned m
forall m. Int -> Int -> Int -> m -> LinePositioned m
LinePositioned Int
p Int
l Int
lp m
suffix, c
s)
   span :: (LinePositioned m -> Bool)
-> (Char -> Bool)
-> LinePositioned m
-> (LinePositioned m, LinePositioned m)
span LinePositioned m -> Bool
ft Char -> Bool
fc (LinePositioned Int
p0 Int
l0 Int
lp0 m
t) = (m, m, (Int, Int, Int)) -> (LinePositioned m, LinePositioned m)
forall m m.
(m, m, (Int, Int, Int)) -> (LinePositioned m, LinePositioned m)
rewrap ((m, m, (Int, Int, Int)) -> (LinePositioned m, LinePositioned m))
-> (m, m, (Int, Int, Int)) -> (LinePositioned m, LinePositioned m)
forall a b. (a -> b) -> a -> b
$ (Int, Int, Int)
-> ((Int, Int, Int) -> m -> Maybe (Int, Int, Int))
-> ((Int, Int, Int) -> Char -> Maybe (Int, Int, Int))
-> m
-> (m, m, (Int, Int, Int))
forall t s.
TextualMonoid t =>
s
-> (s -> t -> Maybe s) -> (s -> Char -> Maybe s) -> t -> (t, t, s)
Textual.spanMaybe' (Int
p0, Int
l0, Int
lp0) (Int, Int, Int) -> m -> Maybe (Int, Int, Int)
ft' (Int, Int, Int) -> Char -> Maybe (Int, Int, Int)
forall a b.
(Integral a, Enum b) =>
(a, b, a) -> Char -> Maybe (a, b, a)
fc' m
t
      where ft' :: (Int, Int, Int) -> m -> Maybe (Int, Int, Int)
ft' (Int
p, Int
l, Int
lp) m
prime = if LinePositioned m -> Bool
ft (Int -> Int -> Int -> m -> LinePositioned m
forall m. Int -> Int -> Int -> m -> LinePositioned m
LinePositioned Int
p Int
l Int
lp m
prime)
                                   then let p' :: Int
p' = Int -> Int
forall a. Enum a => a -> a
succ Int
p
                                        in Int
p' Int -> Maybe (Int, Int, Int) -> Maybe (Int, Int, Int)
`seq` (Int, Int, Int) -> Maybe (Int, Int, Int)
forall a. a -> Maybe a
Just (Int
p', Int
l, Int
lp)
                                   else Maybe (Int, Int, Int)
forall a. Maybe a
Nothing
            fc' :: (a, b, a) -> Char -> Maybe (a, b, a)
fc' (a
p, b
l, a
lp) Char
c | Char -> Bool
fc Char
c = (a, b, a) -> Maybe (a, b, a)
forall a. a -> Maybe a
Just ((a, b, a) -> Maybe (a, b, a)) -> (a, b, a) -> Maybe (a, b, a)
forall a b. (a -> b) -> a -> b
$! a -> (a, b, a) -> (a, b, a)
seq a
p'
                                      ((a, b, a) -> (a, b, a)) -> (a, b, a) -> (a, b, a)
forall a b. (a -> b) -> a -> b
$ if Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'\n' Bool -> Bool -> Bool
|| Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'\f' then b -> (a, b, a) -> (a, b, a)
seq b
l' (a
p', b
l', a
p)
                                        else if Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'\r' then (a
p', b
l, a
p)
                                        else if Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'\t' then (a
p', b
l, a
lp a -> a -> a
forall a. Num a => a -> a -> a
+ (a
p a -> a -> a
forall a. Num a => a -> a -> a
- a
lp) a -> a -> a
forall a. Integral a => a -> a -> a
`mod` a
8 a -> a -> a
forall a. Num a => a -> a -> a
- a
8)
                                        else (a
p', b
l, a
lp)
                             | Bool
otherwise = Maybe (a, b, a)
forall a. Maybe a
Nothing
               where p' :: a
p' = a -> a
forall a. Enum a => a -> a
succ a
p
                     l' :: b
l' = b -> b
forall a. Enum a => a -> a
succ b
l
            rewrap :: (m, m, (Int, Int, Int)) -> (LinePositioned m, LinePositioned m)
rewrap (m
prefix, m
suffix, (Int
p, Int
l, Int
lp)) = (Int -> Int -> Int -> m -> LinePositioned m
forall m. Int -> Int -> Int -> m -> LinePositioned m
LinePositioned Int
p0 Int
l0 Int
lp0 m
prefix, Int -> Int -> Int -> m -> LinePositioned m
forall m. Int -> Int -> Int -> m -> LinePositioned m
LinePositioned Int
p Int
l Int
lp m
suffix)

   scanl :: (Char -> Char -> Char)
-> Char -> LinePositioned m -> LinePositioned m
scanl Char -> Char -> Char
f Char
ch (LinePositioned Int
p Int
l Int
lp m
c) = Int -> Int -> Int -> m -> LinePositioned m
forall m. Int -> Int -> Int -> m -> LinePositioned m
LinePositioned Int
p Int
l Int
lp ((Char -> Char -> Char) -> Char -> m -> m
forall t.
TextualMonoid t =>
(Char -> Char -> Char) -> Char -> t -> t
Textual.scanl Char -> Char -> Char
f Char
ch m
c)
   scanl1 :: (Char -> Char -> Char) -> LinePositioned m -> LinePositioned m
scanl1 Char -> Char -> Char
f (LinePositioned Int
p Int
l Int
lp m
c) = Int -> Int -> Int -> m -> LinePositioned m
forall m. Int -> Int -> Int -> m -> LinePositioned m
LinePositioned Int
p Int
l Int
lp ((Char -> Char -> Char) -> m -> m
forall t. TextualMonoid t => (Char -> Char -> Char) -> t -> t
Textual.scanl1 Char -> Char -> Char
f m
c)
   scanr :: (Char -> Char -> Char)
-> Char -> LinePositioned m -> LinePositioned m
scanr Char -> Char -> Char
f Char
ch (LinePositioned Int
p Int
l Int
lp m
c) = Int -> Int -> Int -> m -> LinePositioned m
forall m. Int -> Int -> Int -> m -> LinePositioned m
LinePositioned Int
p Int
l Int
lp ((Char -> Char -> Char) -> Char -> m -> m
forall t.
TextualMonoid t =>
(Char -> Char -> Char) -> Char -> t -> t
Textual.scanr Char -> Char -> Char
f Char
ch m
c)
   scanr1 :: (Char -> Char -> Char) -> LinePositioned m -> LinePositioned m
scanr1 Char -> Char -> Char
f (LinePositioned Int
p Int
l Int
lp m
c) = Int -> Int -> Int -> m -> LinePositioned m
forall m. Int -> Int -> Int -> m -> LinePositioned m
LinePositioned Int
p Int
l Int
lp ((Char -> Char -> Char) -> m -> m
forall t. TextualMonoid t => (Char -> Char -> Char) -> t -> t
Textual.scanr1 Char -> Char -> Char
f m
c)
   mapAccumL :: (a -> Char -> (a, Char))
-> a -> LinePositioned m -> (a, LinePositioned m)
mapAccumL a -> Char -> (a, Char)
f a
a0 (LinePositioned Int
p Int
l Int
lp m
c) = (m -> LinePositioned m) -> (a, m) -> (a, LinePositioned m)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Int -> Int -> Int -> m -> LinePositioned m
forall m. Int -> Int -> Int -> m -> LinePositioned m
LinePositioned Int
p Int
l Int
lp) ((a -> Char -> (a, Char)) -> a -> m -> (a, m)
forall t a.
TextualMonoid t =>
(a -> Char -> (a, Char)) -> a -> t -> (a, t)
Textual.mapAccumL a -> Char -> (a, Char)
f a
a0 m
c)
   mapAccumR :: (a -> Char -> (a, Char))
-> a -> LinePositioned m -> (a, LinePositioned m)
mapAccumR a -> Char -> (a, Char)
f a
a0 (LinePositioned Int
p Int
l Int
lp m
c) = (m -> LinePositioned m) -> (a, m) -> (a, LinePositioned m)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Int -> Int -> Int -> m -> LinePositioned m
forall m. Int -> Int -> Int -> m -> LinePositioned m
LinePositioned Int
p Int
l Int
lp) ((a -> Char -> (a, Char)) -> a -> m -> (a, m)
forall t a.
TextualMonoid t =>
(a -> Char -> (a, Char)) -> a -> t -> (a, t)
Textual.mapAccumR a -> Char -> (a, Char)
f a
a0 m
c)

   split :: (Char -> Bool) -> LinePositioned m -> [LinePositioned m]
split Char -> Bool
f (LinePositioned Int
p0 Int
l0 Int
lp0 m
c0) = Int -> Int -> Int -> [m] -> [LinePositioned m]
forall m.
TextualMonoid m =>
Int -> Int -> Int -> [m] -> [LinePositioned m]
rewrap Int
p0 Int
l0 Int
lp0 ((Char -> Bool) -> m -> [m]
forall t. TextualMonoid t => (Char -> Bool) -> t -> [t]
Textual.split Char -> Bool
f m
c0)
      where rewrap :: Int -> Int -> Int -> [m] -> [LinePositioned m]
rewrap Int
_ Int
_ Int
_ [] = []
            rewrap Int
p Int
l Int
lp (m
c:[m]
rest) = Int -> Int -> Int -> m -> LinePositioned m
forall m. Int -> Int -> Int -> m -> LinePositioned m
LinePositioned Int
p Int
l Int
lp m
c
                                     LinePositioned m -> [LinePositioned m] -> [LinePositioned m]
forall a. a -> [a] -> [a]
: Int -> Int -> Int -> [m] -> [LinePositioned m]
rewrap Int
p' (Int
l Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
lines) (if Int
lines Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0 then Int
lp else Int
p' Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
columns) [m]
rest
               where p' :: Int
p' = Int
p Int -> Int -> Int
forall a. Num a => a -> a -> a
+ m -> Int
forall m. Factorial m => m -> Int
length m
c
                     (Int
lines, Int
columns) = m -> (Int, Int)
forall m. TextualMonoid m => m -> (Int, Int)
linesColumns m
c
   find :: (Char -> Bool) -> LinePositioned m -> Maybe Char
find Char -> Bool
p = (Char -> Bool) -> m -> Maybe Char
forall t. TextualMonoid t => (Char -> Bool) -> t -> Maybe Char
find Char -> Bool
p (m -> Maybe Char)
-> (LinePositioned m -> m) -> LinePositioned m -> Maybe Char
forall b c a. (b -> c) -> (a -> b) -> a -> c
. LinePositioned m -> m
forall a. LinePositioned a -> a
extractLines

   foldl_ :: (a -> Char -> a) -> a -> LinePositioned m -> a
foldl_ a -> Char -> a
fc a
a0 (LinePositioned Int
_ Int
_ Int
_ m
t) = (a -> Char -> a) -> a -> m -> a
forall t a. TextualMonoid t => (a -> Char -> a) -> a -> t -> a
Textual.foldl_ a -> Char -> a
fc a
a0 m
t
   foldl_' :: (a -> Char -> a) -> a -> LinePositioned m -> a
foldl_' a -> Char -> a
fc a
a0 (LinePositioned Int
_ Int
_ Int
_ m
t) = (a -> Char -> a) -> a -> m -> a
forall t a. TextualMonoid t => (a -> Char -> a) -> a -> t -> a
Textual.foldl_' a -> Char -> a
fc a
a0 m
t
   foldr_ :: (Char -> a -> a) -> a -> LinePositioned m -> a
foldr_ Char -> a -> a
fc a
a0 (LinePositioned Int
_ Int
_ Int
_ m
t) = (Char -> a -> a) -> a -> m -> a
forall t a. TextualMonoid t => (Char -> a -> a) -> a -> t -> a
Textual.foldr_ Char -> a -> a
fc a
a0 m
t

   spanMaybe_ :: s
-> (s -> Char -> Maybe s)
-> LinePositioned m
-> (LinePositioned m, LinePositioned m, s)
spanMaybe_ s
s0 s -> Char -> Maybe s
fc (LinePositioned Int
p0 Int
l0 Int
lp0 m
t) = (m, m, s) -> (LinePositioned m, LinePositioned m, s)
forall m m c.
TextualMonoid m =>
(m, m, c) -> (LinePositioned m, LinePositioned m, c)
rewrap ((m, m, s) -> (LinePositioned m, LinePositioned m, s))
-> (m, m, s) -> (LinePositioned m, LinePositioned m, s)
forall a b. (a -> b) -> a -> b
$ s -> (s -> Char -> Maybe s) -> m -> (m, m, s)
forall t s.
TextualMonoid t =>
s -> (s -> Char -> Maybe s) -> t -> (t, t, s)
Textual.spanMaybe_ s
s0 s -> Char -> Maybe s
fc m
t
      where rewrap :: (m, m, c) -> (LinePositioned m, LinePositioned m, c)
rewrap (m
prefix, m
suffix, c
s) = (Int -> Int -> Int -> m -> LinePositioned m
forall m. Int -> Int -> Int -> m -> LinePositioned m
LinePositioned Int
p0 Int
l0 Int
lp0 m
prefix,
                                          Int -> Int -> Int -> m -> LinePositioned m
forall m. Int -> Int -> Int -> m -> LinePositioned m
LinePositioned Int
p1 (Int
l0 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
l) (if Int
l Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0 then Int
lp0 else Int
p1 Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
col) m
suffix,
                                          c
s)
              where (Int
l, Int
col) = m -> (Int, Int)
forall m. TextualMonoid m => m -> (Int, Int)
linesColumns m
prefix
                    p1 :: Int
p1 = Int
p0 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ m -> Int
forall m. Factorial m => m -> Int
length m
prefix
   spanMaybe_' :: s
-> (s -> Char -> Maybe s)
-> LinePositioned m
-> (LinePositioned m, LinePositioned m, s)
spanMaybe_' s
s0 s -> Char -> Maybe s
fc (LinePositioned Int
p0 Int
l0 Int
lp0 m
t) = (m, m, s) -> (LinePositioned m, LinePositioned m, s)
forall m m c.
TextualMonoid m =>
(m, m, c) -> (LinePositioned m, LinePositioned m, c)
rewrap ((m, m, s) -> (LinePositioned m, LinePositioned m, s))
-> (m, m, s) -> (LinePositioned m, LinePositioned m, s)
forall a b. (a -> b) -> a -> b
$ s -> (s -> Char -> Maybe s) -> m -> (m, m, s)
forall t s.
TextualMonoid t =>
s -> (s -> Char -> Maybe s) -> t -> (t, t, s)
Textual.spanMaybe_' s
s0 s -> Char -> Maybe s
fc m
t
      where rewrap :: (m, m, c) -> (LinePositioned m, LinePositioned m, c)
rewrap (m
prefix, m
suffix, c
s) = Int
p1 Int
-> (LinePositioned m, LinePositioned m, c)
-> (LinePositioned m, LinePositioned m, c)
`seq` Int
l1 Int
-> (LinePositioned m, LinePositioned m, c)
-> (LinePositioned m, LinePositioned m, c)
`seq` Int
lp1 Int
-> (LinePositioned m, LinePositioned m, c)
-> (LinePositioned m, LinePositioned m, c)
`seq`
                                         (Int -> Int -> Int -> m -> LinePositioned m
forall m. Int -> Int -> Int -> m -> LinePositioned m
LinePositioned Int
p0 Int
l0 Int
lp0 m
prefix, Int -> Int -> Int -> m -> LinePositioned m
forall m. Int -> Int -> Int -> m -> LinePositioned m
LinePositioned Int
p1 Int
l1 Int
lp1 m
suffix, c
s)
              where (Int
l, Int
col) = m -> (Int, Int)
forall m. TextualMonoid m => m -> (Int, Int)
linesColumns' m
prefix
                    p1 :: Int
p1 = Int
p0 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ m -> Int
forall m. Factorial m => m -> Int
length m
prefix
                    l1 :: Int
l1 = Int
l0 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
l
                    lp1 :: Int
lp1 = if Int
l Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0 then Int
lp0 else Int
p1 Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
col
   span_ :: Bool
-> (Char -> Bool)
-> LinePositioned m
-> (LinePositioned m, LinePositioned m)
span_ Bool
bt Char -> Bool
fc (LinePositioned Int
p0 Int
l0 Int
lp0 m
t) = (m, m) -> (LinePositioned m, LinePositioned m)
forall m m.
TextualMonoid m =>
(m, m) -> (LinePositioned m, LinePositioned m)
rewrap ((m, m) -> (LinePositioned m, LinePositioned m))
-> (m, m) -> (LinePositioned m, LinePositioned m)
forall a b. (a -> b) -> a -> b
$ Bool -> (Char -> Bool) -> m -> (m, m)
forall t. TextualMonoid t => Bool -> (Char -> Bool) -> t -> (t, t)
Textual.span_ Bool
bt Char -> Bool
fc m
t
      where rewrap :: (m, m) -> (LinePositioned m, LinePositioned m)
rewrap (m
prefix, m
suffix) = (Int -> Int -> Int -> m -> LinePositioned m
forall m. Int -> Int -> Int -> m -> LinePositioned m
LinePositioned Int
p0 Int
l0 Int
lp0 m
prefix,
                                       Int -> Int -> Int -> m -> LinePositioned m
forall m. Int -> Int -> Int -> m -> LinePositioned m
LinePositioned Int
p1 (Int
l0 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
l) (if Int
l Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0 then Int
lp0 else Int
p1 Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
col) m
suffix)
              where (Int
l, Int
col) = m -> (Int, Int)
forall m. TextualMonoid m => m -> (Int, Int)
linesColumns' m
prefix
                    p1 :: Int
p1 = Int
p0 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ m -> Int
forall m. Factorial m => m -> Int
length m
prefix
   break_ :: Bool
-> (Char -> Bool)
-> LinePositioned m
-> (LinePositioned m, LinePositioned m)
break_ Bool
bt Char -> Bool
fc LinePositioned m
t = Bool
-> (Char -> Bool)
-> LinePositioned m
-> (LinePositioned m, LinePositioned m)
forall t. TextualMonoid t => Bool -> (Char -> Bool) -> t -> (t, t)
span_ (Bool -> Bool
not Bool
bt) (Bool -> Bool
not (Bool -> Bool) -> (Char -> Bool) -> Char -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> Bool
fc) LinePositioned m
t
   dropWhile_ :: Bool -> (Char -> Bool) -> LinePositioned m -> LinePositioned m
dropWhile_ Bool
bt Char -> Bool
fc LinePositioned m
t = (LinePositioned m, LinePositioned m) -> LinePositioned m
forall a b. (a, b) -> b
snd (Bool
-> (Char -> Bool)
-> LinePositioned m
-> (LinePositioned m, LinePositioned m)
forall t. TextualMonoid t => Bool -> (Char -> Bool) -> t -> (t, t)
span_ Bool
bt Char -> Bool
fc LinePositioned m
t)
   takeWhile_ :: Bool -> (Char -> Bool) -> LinePositioned m -> LinePositioned m
takeWhile_ Bool
bt Char -> Bool
fc (LinePositioned Int
p Int
l Int
lp m
t) = Int -> Int -> Int -> m -> LinePositioned m
forall m. Int -> Int -> Int -> m -> LinePositioned m
LinePositioned Int
p Int
l Int
lp (Bool -> (Char -> Bool) -> m -> m
forall t. TextualMonoid t => Bool -> (Char -> Bool) -> t -> t
takeWhile_ Bool
bt Char -> Bool
fc m
t)
   toString :: (LinePositioned m -> String) -> LinePositioned m -> String
toString LinePositioned m -> String
ft LinePositioned m
lpt = (m -> String) -> m -> String
forall t. TextualMonoid t => (t -> String) -> t -> String
toString (LinePositioned m -> String
ft (LinePositioned m -> String)
-> (m -> LinePositioned m) -> m -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. m -> LinePositioned m
forall (f :: * -> *) a. Applicative f => a -> f a
pure) (LinePositioned m -> m
forall a. LinePositioned a -> a
extractLines LinePositioned m
lpt)
   toText :: (LinePositioned m -> Text) -> LinePositioned m -> Text
toText LinePositioned m -> Text
ft LinePositioned m
lpt = (m -> Text) -> m -> Text
forall t. TextualMonoid t => (t -> Text) -> t -> Text
toText (LinePositioned m -> Text
ft (LinePositioned m -> Text) -> (m -> LinePositioned m) -> m -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. m -> LinePositioned m
forall (f :: * -> *) a. Applicative f => a -> f a
pure) (LinePositioned m -> m
forall a. LinePositioned a -> a
extractLines LinePositioned m
lpt)

   {-# INLINE characterPrefix #-}
   {-# INLINE splitCharacterPrefix #-}
   {-# INLINE map #-}
   {-# INLINE concatMap #-}
   {-# INLINE foldl' #-}
   {-# INLINE foldr #-}
   {-# INLINE spanMaybe' #-}
   {-# INLINE span #-}
   {-# INLINE split #-}
   {-# INLINE find #-}
   {-# INLINE foldl_' #-}
   {-# INLINE foldr_ #-}
   {-# INLINE any #-}
   {-# INLINE all #-}
   {-# INLINE spanMaybe_' #-}
   {-# INLINE span_ #-}
   {-# INLINE break_ #-}
   {-# INLINE dropWhile_ #-}
   {-# INLINE takeWhile_ #-}

linesColumns :: TextualMonoid m => m -> (Int, Int)
linesColumns :: m -> (Int, Int)
linesColumns m
t = ((Int, Int) -> m -> (Int, Int))
-> ((Int, Int) -> Char -> (Int, Int))
-> (Int, Int)
-> m
-> (Int, Int)
forall t a.
TextualMonoid t =>
(a -> t -> a) -> (a -> Char -> a) -> a -> t -> a
Textual.foldl ((Int, Int) -> m -> (Int, Int)
forall a b. a -> b -> a
const ((Int, Int) -> m -> (Int, Int))
-> ((Int, Int) -> (Int, Int)) -> (Int, Int) -> m -> (Int, Int)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int -> Int) -> (Int, Int) -> (Int, Int)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Int -> Int
forall a. Enum a => a -> a
succ) (Int, Int) -> Char -> (Int, Int)
forall a a. (Integral a, Enum a) => (a, a) -> Char -> (a, a)
fc (Int
0, Int
1) m
t
   where fc :: (a, a) -> Char -> (a, a)
fc (a
l, a
_) Char
'\n' = (a -> a
forall a. Enum a => a -> a
succ a
l, a
1)
         fc (a
l, a
_) Char
'\f' = (a -> a
forall a. Enum a => a -> a
succ a
l, a
1)
         fc (a
l, a
_) Char
'\r' = (a
l, a
1)
         fc (a
l, a
c) Char
'\t' = (a
l, a
c a -> a -> a
forall a. Num a => a -> a -> a
+ a
9 a -> a -> a
forall a. Num a => a -> a -> a
- a
c a -> a -> a
forall a. Integral a => a -> a -> a
`mod` a
8)
         fc (a
l, a
c) Char
_ = (a
l, a -> a
forall a. Enum a => a -> a
succ a
c)
linesColumns' :: TextualMonoid m => m -> (Int, Int)
linesColumns' :: m -> (Int, Int)
linesColumns' m
t = ((Int, Int) -> m -> (Int, Int))
-> ((Int, Int) -> Char -> (Int, Int))
-> (Int, Int)
-> m
-> (Int, Int)
forall t a.
TextualMonoid t =>
(a -> t -> a) -> (a -> Char -> a) -> a -> t -> a
Textual.foldl' ((Int, Int) -> m -> (Int, Int)
forall a b. a -> b -> a
const ((Int, Int) -> m -> (Int, Int))
-> ((Int, Int) -> (Int, Int)) -> (Int, Int) -> m -> (Int, Int)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int -> Int) -> (Int, Int) -> (Int, Int)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Int -> Int
forall a. Enum a => a -> a
succ) (Int, Int) -> Char -> (Int, Int)
forall a a. (Integral a, Enum a) => (a, a) -> Char -> (a, a)
fc (Int
0, Int
1) m
t
   where fc :: (a, b) -> Char -> (a, b)
fc (a
l, b
_) Char
'\n' = let l' :: a
l' = a -> a
forall a. Enum a => a -> a
succ a
l in a -> (a, b) -> (a, b)
seq a
l' (a
l', b
1)
         fc (a
l, b
_) Char
'\f' = let l' :: a
l' = a -> a
forall a. Enum a => a -> a
succ a
l in a -> (a, b) -> (a, b)
seq a
l' (a
l', b
1)
         fc (a
l, b
_) Char
'\r' = (a
l, b
1)
         fc (a
l, b
c) Char
'\t' = (a
l, b
c b -> b -> b
forall a. Num a => a -> a -> a
+ b
9 b -> b -> b
forall a. Num a => a -> a -> a
- b
c b -> b -> b
forall a. Integral a => a -> a -> a
`mod` b
8)
         fc (a
l, b
c) Char
_ = let c' :: b
c' = b -> b
forall a. Enum a => a -> a
succ b
c in b -> (a, b) -> (a, b)
seq b
c' (a
l, b
c')
{-# INLINE linesColumns #-}
{-# INLINE linesColumns' #-}

const3 :: a -> b -> c -> d -> a
const3 :: a -> b -> c -> d -> a
const3 a
a b
_p c
_l d
_lp = a
a
{-# INLINE const3 #-}

fstOf4 :: (a, b, c, d) -> a
fstOf4 :: (a, b, c, d) -> a
fstOf4 (a
a, b
_, c
_, d
_) = a
a
{-# INLINE fstOf4  #-}