{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE CPP #-}

-- Copyright 2008 JP Bernardy
-- | Basic types useful everywhere we play with buffers.
module Yi.Buffer.Basic where

import Data.Binary
import Data.Typeable
import GHC.Generics (Generic)
import Data.Ix
import Data.Default
import Yi.Utils

-- | Direction of movement inside a buffer
data Direction = Backward | Forward
    deriving (Direction -> Direction -> Bool
(Direction -> Direction -> Bool)
-> (Direction -> Direction -> Bool) -> Eq Direction
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Direction -> Direction -> Bool
$c/= :: Direction -> Direction -> Bool
== :: Direction -> Direction -> Bool
$c== :: Direction -> Direction -> Bool
Eq, Eq Direction
Eq Direction
-> (Direction -> Direction -> Ordering)
-> (Direction -> Direction -> Bool)
-> (Direction -> Direction -> Bool)
-> (Direction -> Direction -> Bool)
-> (Direction -> Direction -> Bool)
-> (Direction -> Direction -> Direction)
-> (Direction -> Direction -> Direction)
-> Ord Direction
Direction -> Direction -> Bool
Direction -> Direction -> Ordering
Direction -> Direction -> Direction
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Direction -> Direction -> Direction
$cmin :: Direction -> Direction -> Direction
max :: Direction -> Direction -> Direction
$cmax :: Direction -> Direction -> Direction
>= :: Direction -> Direction -> Bool
$c>= :: Direction -> Direction -> Bool
> :: Direction -> Direction -> Bool
$c> :: Direction -> Direction -> Bool
<= :: Direction -> Direction -> Bool
$c<= :: Direction -> Direction -> Bool
< :: Direction -> Direction -> Bool
$c< :: Direction -> Direction -> Bool
compare :: Direction -> Direction -> Ordering
$ccompare :: Direction -> Direction -> Ordering
$cp1Ord :: Eq Direction
Ord, Typeable, Int -> Direction -> ShowS
[Direction] -> ShowS
Direction -> String
(Int -> Direction -> ShowS)
-> (Direction -> String)
-> ([Direction] -> ShowS)
-> Show Direction
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Direction] -> ShowS
$cshowList :: [Direction] -> ShowS
show :: Direction -> String
$cshow :: Direction -> String
showsPrec :: Int -> Direction -> ShowS
$cshowsPrec :: Int -> Direction -> ShowS
Show, Direction
Direction -> Direction -> Bounded Direction
forall a. a -> a -> Bounded a
maxBound :: Direction
$cmaxBound :: Direction
minBound :: Direction
$cminBound :: Direction
Bounded, Int -> Direction
Direction -> Int
Direction -> [Direction]
Direction -> Direction
Direction -> Direction -> [Direction]
Direction -> Direction -> Direction -> [Direction]
(Direction -> Direction)
-> (Direction -> Direction)
-> (Int -> Direction)
-> (Direction -> Int)
-> (Direction -> [Direction])
-> (Direction -> Direction -> [Direction])
-> (Direction -> Direction -> [Direction])
-> (Direction -> Direction -> Direction -> [Direction])
-> Enum Direction
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: Direction -> Direction -> Direction -> [Direction]
$cenumFromThenTo :: Direction -> Direction -> Direction -> [Direction]
enumFromTo :: Direction -> Direction -> [Direction]
$cenumFromTo :: Direction -> Direction -> [Direction]
enumFromThen :: Direction -> Direction -> [Direction]
$cenumFromThen :: Direction -> Direction -> [Direction]
enumFrom :: Direction -> [Direction]
$cenumFrom :: Direction -> [Direction]
fromEnum :: Direction -> Int
$cfromEnum :: Direction -> Int
toEnum :: Int -> Direction
$ctoEnum :: Int -> Direction
pred :: Direction -> Direction
$cpred :: Direction -> Direction
succ :: Direction -> Direction
$csucc :: Direction -> Direction
Enum, (forall x. Direction -> Rep Direction x)
-> (forall x. Rep Direction x -> Direction) -> Generic Direction
forall x. Rep Direction x -> Direction
forall x. Direction -> Rep Direction x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Direction x -> Direction
$cfrom :: forall x. Direction -> Rep Direction x
Generic)

instance Binary Direction

reverseDir :: Direction -> Direction
reverseDir :: Direction -> Direction
reverseDir Direction
Forward = Direction
Backward
reverseDir Direction
Backward = Direction
Forward


-- | reverse if Backward
mayReverse :: Direction -> [a] -> [a]
mayReverse :: Direction -> [a] -> [a]
mayReverse Direction
Forward = [a] -> [a]
forall a. a -> a
id
mayReverse Direction
Backward = [a] -> [a]
forall a. [a] -> [a]
reverse

-- | 'direction' is in the same style of 'maybe' or 'either' functions,
-- It takes one argument per direction (backward, then forward) and a
-- direction to select the output.
directionElim :: Direction -> a -> a -> a
directionElim :: Direction -> a -> a -> a
directionElim Direction
Backward a
b a
_ = a
b
directionElim Direction
Forward  a
_ a
f = a
f

-- | A mark in a buffer
newtype Mark = Mark {Mark -> Int
markId::Int} deriving (Mark -> Mark -> Bool
(Mark -> Mark -> Bool) -> (Mark -> Mark -> Bool) -> Eq Mark
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Mark -> Mark -> Bool
$c/= :: Mark -> Mark -> Bool
== :: Mark -> Mark -> Bool
$c== :: Mark -> Mark -> Bool
Eq, Eq Mark
Eq Mark
-> (Mark -> Mark -> Ordering)
-> (Mark -> Mark -> Bool)
-> (Mark -> Mark -> Bool)
-> (Mark -> Mark -> Bool)
-> (Mark -> Mark -> Bool)
-> (Mark -> Mark -> Mark)
-> (Mark -> Mark -> Mark)
-> Ord Mark
Mark -> Mark -> Bool
Mark -> Mark -> Ordering
Mark -> Mark -> Mark
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Mark -> Mark -> Mark
$cmin :: Mark -> Mark -> Mark
max :: Mark -> Mark -> Mark
$cmax :: Mark -> Mark -> Mark
>= :: Mark -> Mark -> Bool
$c>= :: Mark -> Mark -> Bool
> :: Mark -> Mark -> Bool
$c> :: Mark -> Mark -> Bool
<= :: Mark -> Mark -> Bool
$c<= :: Mark -> Mark -> Bool
< :: Mark -> Mark -> Bool
$c< :: Mark -> Mark -> Bool
compare :: Mark -> Mark -> Ordering
$ccompare :: Mark -> Mark -> Ordering
$cp1Ord :: Eq Mark
Ord, Int -> Mark -> ShowS
[Mark] -> ShowS
Mark -> String
(Int -> Mark -> ShowS)
-> (Mark -> String) -> ([Mark] -> ShowS) -> Show Mark
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Mark] -> ShowS
$cshowList :: [Mark] -> ShowS
show :: Mark -> String
$cshow :: Mark -> String
showsPrec :: Int -> Mark -> ShowS
$cshowsPrec :: Int -> Mark -> ShowS
Show, Typeable, Get Mark
[Mark] -> Put
Mark -> Put
(Mark -> Put) -> Get Mark -> ([Mark] -> Put) -> Binary Mark
forall t. (t -> Put) -> Get t -> ([t] -> Put) -> Binary t
putList :: [Mark] -> Put
$cputList :: [Mark] -> Put
get :: Get Mark
$cget :: Get Mark
put :: Mark -> Put
$cput :: Mark -> Put
Binary)

-- | Reference to a buffer.
newtype BufferRef = BufferRef Int
    deriving (BufferRef -> BufferRef -> Bool
(BufferRef -> BufferRef -> Bool)
-> (BufferRef -> BufferRef -> Bool) -> Eq BufferRef
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BufferRef -> BufferRef -> Bool
$c/= :: BufferRef -> BufferRef -> Bool
== :: BufferRef -> BufferRef -> Bool
$c== :: BufferRef -> BufferRef -> Bool
Eq, Eq BufferRef
Eq BufferRef
-> (BufferRef -> BufferRef -> Ordering)
-> (BufferRef -> BufferRef -> Bool)
-> (BufferRef -> BufferRef -> Bool)
-> (BufferRef -> BufferRef -> Bool)
-> (BufferRef -> BufferRef -> Bool)
-> (BufferRef -> BufferRef -> BufferRef)
-> (BufferRef -> BufferRef -> BufferRef)
-> Ord BufferRef
BufferRef -> BufferRef -> Bool
BufferRef -> BufferRef -> Ordering
BufferRef -> BufferRef -> BufferRef
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: BufferRef -> BufferRef -> BufferRef
$cmin :: BufferRef -> BufferRef -> BufferRef
max :: BufferRef -> BufferRef -> BufferRef
$cmax :: BufferRef -> BufferRef -> BufferRef
>= :: BufferRef -> BufferRef -> Bool
$c>= :: BufferRef -> BufferRef -> Bool
> :: BufferRef -> BufferRef -> Bool
$c> :: BufferRef -> BufferRef -> Bool
<= :: BufferRef -> BufferRef -> Bool
$c<= :: BufferRef -> BufferRef -> Bool
< :: BufferRef -> BufferRef -> Bool
$c< :: BufferRef -> BufferRef -> Bool
compare :: BufferRef -> BufferRef -> Ordering
$ccompare :: BufferRef -> BufferRef -> Ordering
$cp1Ord :: Eq BufferRef
Ord, Typeable, Get BufferRef
[BufferRef] -> Put
BufferRef -> Put
(BufferRef -> Put)
-> Get BufferRef -> ([BufferRef] -> Put) -> Binary BufferRef
forall t. (t -> Put) -> Get t -> ([t] -> Put) -> Binary t
putList :: [BufferRef] -> Put
$cputList :: [BufferRef] -> Put
get :: Get BufferRef
$cget :: Get BufferRef
put :: BufferRef -> Put
$cput :: BufferRef -> Put
Binary,
              Integer -> BufferRef
BufferRef -> BufferRef
BufferRef -> BufferRef -> BufferRef
(BufferRef -> BufferRef -> BufferRef)
-> (BufferRef -> BufferRef -> BufferRef)
-> (BufferRef -> BufferRef -> BufferRef)
-> (BufferRef -> BufferRef)
-> (BufferRef -> BufferRef)
-> (BufferRef -> BufferRef)
-> (Integer -> BufferRef)
-> Num BufferRef
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
fromInteger :: Integer -> BufferRef
$cfromInteger :: Integer -> BufferRef
signum :: BufferRef -> BufferRef
$csignum :: BufferRef -> BufferRef
abs :: BufferRef -> BufferRef
$cabs :: BufferRef -> BufferRef
negate :: BufferRef -> BufferRef
$cnegate :: BufferRef -> BufferRef
* :: BufferRef -> BufferRef -> BufferRef
$c* :: BufferRef -> BufferRef -> BufferRef
- :: BufferRef -> BufferRef -> BufferRef
$c- :: BufferRef -> BufferRef -> BufferRef
+ :: BufferRef -> BufferRef -> BufferRef
$c+ :: BufferRef -> BufferRef -> BufferRef
Num)

instance Show BufferRef where
    show :: BufferRef -> String
show (BufferRef Int
r) = String
"B#" String -> ShowS
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
r

-- | A point in a buffer
newtype Point = Point {Point -> Int
fromPoint :: Int}           -- offset in the buffer (#codepoints, NOT bytes)
    deriving (Point -> Point -> Bool
(Point -> Point -> Bool) -> (Point -> Point -> Bool) -> Eq Point
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Point -> Point -> Bool
$c/= :: Point -> Point -> Bool
== :: Point -> Point -> Bool
$c== :: Point -> Point -> Bool
Eq, Eq Point
Eq Point
-> (Point -> Point -> Ordering)
-> (Point -> Point -> Bool)
-> (Point -> Point -> Bool)
-> (Point -> Point -> Bool)
-> (Point -> Point -> Bool)
-> (Point -> Point -> Point)
-> (Point -> Point -> Point)
-> Ord Point
Point -> Point -> Bool
Point -> Point -> Ordering
Point -> Point -> Point
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Point -> Point -> Point
$cmin :: Point -> Point -> Point
max :: Point -> Point -> Point
$cmax :: Point -> Point -> Point
>= :: Point -> Point -> Bool
$c>= :: Point -> Point -> Bool
> :: Point -> Point -> Bool
$c> :: Point -> Point -> Bool
<= :: Point -> Point -> Bool
$c<= :: Point -> Point -> Bool
< :: Point -> Point -> Bool
$c< :: Point -> Point -> Bool
compare :: Point -> Point -> Ordering
$ccompare :: Point -> Point -> Ordering
$cp1Ord :: Eq Point
Ord, Int -> Point
Point -> Int
Point -> [Point]
Point -> Point
Point -> Point -> [Point]
Point -> Point -> Point -> [Point]
(Point -> Point)
-> (Point -> Point)
-> (Int -> Point)
-> (Point -> Int)
-> (Point -> [Point])
-> (Point -> Point -> [Point])
-> (Point -> Point -> [Point])
-> (Point -> Point -> Point -> [Point])
-> Enum Point
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: Point -> Point -> Point -> [Point]
$cenumFromThenTo :: Point -> Point -> Point -> [Point]
enumFromTo :: Point -> Point -> [Point]
$cenumFromTo :: Point -> Point -> [Point]
enumFromThen :: Point -> Point -> [Point]
$cenumFromThen :: Point -> Point -> [Point]
enumFrom :: Point -> [Point]
$cenumFrom :: Point -> [Point]
fromEnum :: Point -> Int
$cfromEnum :: Point -> Int
toEnum :: Int -> Point
$ctoEnum :: Int -> Point
pred :: Point -> Point
$cpred :: Point -> Point
succ :: Point -> Point
$csucc :: Point -> Point
Enum, Point
Point -> Point -> Bounded Point
forall a. a -> a -> Bounded a
maxBound :: Point
$cmaxBound :: Point
minBound :: Point
$cminBound :: Point
Bounded, Typeable, Get Point
[Point] -> Put
Point -> Put
(Point -> Put) -> Get Point -> ([Point] -> Put) -> Binary Point
forall t. (t -> Put) -> Get t -> ([t] -> Put) -> Binary t
putList :: [Point] -> Put
$cputList :: [Point] -> Put
get :: Get Point
$cget :: Get Point
put :: Point -> Put
$cput :: Point -> Put
Binary, Ord Point
Ord Point
-> ((Point, Point) -> [Point])
-> ((Point, Point) -> Point -> Int)
-> ((Point, Point) -> Point -> Int)
-> ((Point, Point) -> Point -> Bool)
-> ((Point, Point) -> Int)
-> ((Point, Point) -> Int)
-> Ix Point
(Point, Point) -> Int
(Point, Point) -> [Point]
(Point, Point) -> Point -> Bool
(Point, Point) -> Point -> Int
forall a.
Ord a
-> ((a, a) -> [a])
-> ((a, a) -> a -> Int)
-> ((a, a) -> a -> Int)
-> ((a, a) -> a -> Bool)
-> ((a, a) -> Int)
-> ((a, a) -> Int)
-> Ix a
unsafeRangeSize :: (Point, Point) -> Int
$cunsafeRangeSize :: (Point, Point) -> Int
rangeSize :: (Point, Point) -> Int
$crangeSize :: (Point, Point) -> Int
inRange :: (Point, Point) -> Point -> Bool
$cinRange :: (Point, Point) -> Point -> Bool
unsafeIndex :: (Point, Point) -> Point -> Int
$cunsafeIndex :: (Point, Point) -> Point -> Int
index :: (Point, Point) -> Point -> Int
$cindex :: (Point, Point) -> Point -> Int
range :: (Point, Point) -> [Point]
$crange :: (Point, Point) -> [Point]
$cp1Ix :: Ord Point
Ix,
              Integer -> Point
Point -> Point
Point -> Point -> Point
(Point -> Point -> Point)
-> (Point -> Point -> Point)
-> (Point -> Point -> Point)
-> (Point -> Point)
-> (Point -> Point)
-> (Point -> Point)
-> (Integer -> Point)
-> Num Point
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
fromInteger :: Integer -> Point
$cfromInteger :: Integer -> Point
signum :: Point -> Point
$csignum :: Point -> Point
abs :: Point -> Point
$cabs :: Point -> Point
negate :: Point -> Point
$cnegate :: Point -> Point
* :: Point -> Point -> Point
$c* :: Point -> Point -> Point
- :: Point -> Point -> Point
$c- :: Point -> Point -> Point
+ :: Point -> Point -> Point
$c+ :: Point -> Point -> Point
Num, Num Point
Ord Point
Num Point -> Ord Point -> (Point -> Rational) -> Real Point
Point -> Rational
forall a. Num a -> Ord a -> (a -> Rational) -> Real a
toRational :: Point -> Rational
$ctoRational :: Point -> Rational
$cp2Real :: Ord Point
$cp1Real :: Num Point
Real, Enum Point
Real Point
Real Point
-> Enum Point
-> (Point -> Point -> Point)
-> (Point -> Point -> Point)
-> (Point -> Point -> Point)
-> (Point -> Point -> Point)
-> (Point -> Point -> (Point, Point))
-> (Point -> Point -> (Point, Point))
-> (Point -> Integer)
-> Integral Point
Point -> Integer
Point -> Point -> (Point, Point)
Point -> Point -> Point
forall a.
Real a
-> Enum a
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> (a, a))
-> (a -> a -> (a, a))
-> (a -> Integer)
-> Integral a
toInteger :: Point -> Integer
$ctoInteger :: Point -> Integer
divMod :: Point -> Point -> (Point, Point)
$cdivMod :: Point -> Point -> (Point, Point)
quotRem :: Point -> Point -> (Point, Point)
$cquotRem :: Point -> Point -> (Point, Point)
mod :: Point -> Point -> Point
$cmod :: Point -> Point -> Point
div :: Point -> Point -> Point
$cdiv :: Point -> Point -> Point
rem :: Point -> Point -> Point
$crem :: Point -> Point -> Point
quot :: Point -> Point -> Point
$cquot :: Point -> Point -> Point
$cp2Integral :: Enum Point
$cp1Integral :: Real Point
Integral)

instance Show Point where
    show :: Point -> String
show (Point Int
p) = Int -> String
forall a. Show a => a -> String
show Int
p

-- | Size of a buffer region
newtype Size = Size {Size -> Int
fromSize :: Int}             -- size in bytes (#bytes, NOT codepoints)
    deriving (Int -> Size -> ShowS
[Size] -> ShowS
Size -> String
(Int -> Size -> ShowS)
-> (Size -> String) -> ([Size] -> ShowS) -> Show Size
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Size] -> ShowS
$cshowList :: [Size] -> ShowS
show :: Size -> String
$cshow :: Size -> String
showsPrec :: Int -> Size -> ShowS
$cshowsPrec :: Int -> Size -> ShowS
Show, Size -> Size -> Bool
(Size -> Size -> Bool) -> (Size -> Size -> Bool) -> Eq Size
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Size -> Size -> Bool
$c/= :: Size -> Size -> Bool
== :: Size -> Size -> Bool
$c== :: Size -> Size -> Bool
Eq, Eq Size
Eq Size
-> (Size -> Size -> Ordering)
-> (Size -> Size -> Bool)
-> (Size -> Size -> Bool)
-> (Size -> Size -> Bool)
-> (Size -> Size -> Bool)
-> (Size -> Size -> Size)
-> (Size -> Size -> Size)
-> Ord Size
Size -> Size -> Bool
Size -> Size -> Ordering
Size -> Size -> Size
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Size -> Size -> Size
$cmin :: Size -> Size -> Size
max :: Size -> Size -> Size
$cmax :: Size -> Size -> Size
>= :: Size -> Size -> Bool
$c>= :: Size -> Size -> Bool
> :: Size -> Size -> Bool
$c> :: Size -> Size -> Bool
<= :: Size -> Size -> Bool
$c<= :: Size -> Size -> Bool
< :: Size -> Size -> Bool
$c< :: Size -> Size -> Bool
compare :: Size -> Size -> Ordering
$ccompare :: Size -> Size -> Ordering
$cp1Ord :: Eq Size
Ord, Integer -> Size
Size -> Size
Size -> Size -> Size
(Size -> Size -> Size)
-> (Size -> Size -> Size)
-> (Size -> Size -> Size)
-> (Size -> Size)
-> (Size -> Size)
-> (Size -> Size)
-> (Integer -> Size)
-> Num Size
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
fromInteger :: Integer -> Size
$cfromInteger :: Integer -> Size
signum :: Size -> Size
$csignum :: Size -> Size
abs :: Size -> Size
$cabs :: Size -> Size
negate :: Size -> Size
$cnegate :: Size -> Size
* :: Size -> Size -> Size
$c* :: Size -> Size -> Size
- :: Size -> Size -> Size
$c- :: Size -> Size -> Size
+ :: Size -> Size -> Size
$c+ :: Size -> Size -> Size
Num, Int -> Size
Size -> Int
Size -> [Size]
Size -> Size
Size -> Size -> [Size]
Size -> Size -> Size -> [Size]
(Size -> Size)
-> (Size -> Size)
-> (Int -> Size)
-> (Size -> Int)
-> (Size -> [Size])
-> (Size -> Size -> [Size])
-> (Size -> Size -> [Size])
-> (Size -> Size -> Size -> [Size])
-> Enum Size
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: Size -> Size -> Size -> [Size]
$cenumFromThenTo :: Size -> Size -> Size -> [Size]
enumFromTo :: Size -> Size -> [Size]
$cenumFromTo :: Size -> Size -> [Size]
enumFromThen :: Size -> Size -> [Size]
$cenumFromThen :: Size -> Size -> [Size]
enumFrom :: Size -> [Size]
$cenumFrom :: Size -> [Size]
fromEnum :: Size -> Int
$cfromEnum :: Size -> Int
toEnum :: Int -> Size
$ctoEnum :: Int -> Size
pred :: Size -> Size
$cpred :: Size -> Size
succ :: Size -> Size
$csucc :: Size -> Size
Enum, Num Size
Ord Size
Num Size -> Ord Size -> (Size -> Rational) -> Real Size
Size -> Rational
forall a. Num a -> Ord a -> (a -> Rational) -> Real a
toRational :: Size -> Rational
$ctoRational :: Size -> Rational
$cp2Real :: Ord Size
$cp1Real :: Num Size
Real, Enum Size
Real Size
Real Size
-> Enum Size
-> (Size -> Size -> Size)
-> (Size -> Size -> Size)
-> (Size -> Size -> Size)
-> (Size -> Size -> Size)
-> (Size -> Size -> (Size, Size))
-> (Size -> Size -> (Size, Size))
-> (Size -> Integer)
-> Integral Size
Size -> Integer
Size -> Size -> (Size, Size)
Size -> Size -> Size
forall a.
Real a
-> Enum a
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> (a, a))
-> (a -> a -> (a, a))
-> (a -> Integer)
-> Integral a
toInteger :: Size -> Integer
$ctoInteger :: Size -> Integer
divMod :: Size -> Size -> (Size, Size)
$cdivMod :: Size -> Size -> (Size, Size)
quotRem :: Size -> Size -> (Size, Size)
$cquotRem :: Size -> Size -> (Size, Size)
mod :: Size -> Size -> Size
$cmod :: Size -> Size -> Size
div :: Size -> Size -> Size
$cdiv :: Size -> Size -> Size
rem :: Size -> Size -> Size
$crem :: Size -> Size -> Size
quot :: Size -> Size -> Size
$cquot :: Size -> Size -> Size
$cp2Integral :: Enum Size
$cp1Integral :: Real Size
Integral, Get Size
[Size] -> Put
Size -> Put
(Size -> Put) -> Get Size -> ([Size] -> Put) -> Binary Size
forall t. (t -> Put) -> Get t -> ([t] -> Put) -> Binary t
putList :: [Size] -> Put
$cputList :: [Size] -> Put
get :: Get Size
$cget :: Get Size
put :: Size -> Put
$cput :: Size -> Put
Binary)

instance SemiNum Point Size where
    Point Int
p +~ :: Point -> Size -> Point
+~ Size Int
s = Int -> Point
Point (Int
p Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
s)
    Point Int
p -~ :: Point -> Size -> Point
-~ Size Int
s = Int -> Point
Point (Int
p Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
s)
    Point Int
p ~- :: Point -> Point -> Size
~- Point Int
q = Int -> Size
Size (Int -> Int
forall a. Num a => a -> a
abs (Int
p Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
q))

-- | Window references
newtype WindowRef = WindowRef { WindowRef -> Int
unWindowRef :: Int }
  deriving(WindowRef -> WindowRef -> Bool
(WindowRef -> WindowRef -> Bool)
-> (WindowRef -> WindowRef -> Bool) -> Eq WindowRef
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: WindowRef -> WindowRef -> Bool
$c/= :: WindowRef -> WindowRef -> Bool
== :: WindowRef -> WindowRef -> Bool
$c== :: WindowRef -> WindowRef -> Bool
Eq, Eq WindowRef
Eq WindowRef
-> (WindowRef -> WindowRef -> Ordering)
-> (WindowRef -> WindowRef -> Bool)
-> (WindowRef -> WindowRef -> Bool)
-> (WindowRef -> WindowRef -> Bool)
-> (WindowRef -> WindowRef -> Bool)
-> (WindowRef -> WindowRef -> WindowRef)
-> (WindowRef -> WindowRef -> WindowRef)
-> Ord WindowRef
WindowRef -> WindowRef -> Bool
WindowRef -> WindowRef -> Ordering
WindowRef -> WindowRef -> WindowRef
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: WindowRef -> WindowRef -> WindowRef
$cmin :: WindowRef -> WindowRef -> WindowRef
max :: WindowRef -> WindowRef -> WindowRef
$cmax :: WindowRef -> WindowRef -> WindowRef
>= :: WindowRef -> WindowRef -> Bool
$c>= :: WindowRef -> WindowRef -> Bool
> :: WindowRef -> WindowRef -> Bool
$c> :: WindowRef -> WindowRef -> Bool
<= :: WindowRef -> WindowRef -> Bool
$c<= :: WindowRef -> WindowRef -> Bool
< :: WindowRef -> WindowRef -> Bool
$c< :: WindowRef -> WindowRef -> Bool
compare :: WindowRef -> WindowRef -> Ordering
$ccompare :: WindowRef -> WindowRef -> Ordering
$cp1Ord :: Eq WindowRef
Ord, Int -> WindowRef
WindowRef -> Int
WindowRef -> [WindowRef]
WindowRef -> WindowRef
WindowRef -> WindowRef -> [WindowRef]
WindowRef -> WindowRef -> WindowRef -> [WindowRef]
(WindowRef -> WindowRef)
-> (WindowRef -> WindowRef)
-> (Int -> WindowRef)
-> (WindowRef -> Int)
-> (WindowRef -> [WindowRef])
-> (WindowRef -> WindowRef -> [WindowRef])
-> (WindowRef -> WindowRef -> [WindowRef])
-> (WindowRef -> WindowRef -> WindowRef -> [WindowRef])
-> Enum WindowRef
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: WindowRef -> WindowRef -> WindowRef -> [WindowRef]
$cenumFromThenTo :: WindowRef -> WindowRef -> WindowRef -> [WindowRef]
enumFromTo :: WindowRef -> WindowRef -> [WindowRef]
$cenumFromTo :: WindowRef -> WindowRef -> [WindowRef]
enumFromThen :: WindowRef -> WindowRef -> [WindowRef]
$cenumFromThen :: WindowRef -> WindowRef -> [WindowRef]
enumFrom :: WindowRef -> [WindowRef]
$cenumFrom :: WindowRef -> [WindowRef]
fromEnum :: WindowRef -> Int
$cfromEnum :: WindowRef -> Int
toEnum :: Int -> WindowRef
$ctoEnum :: Int -> WindowRef
pred :: WindowRef -> WindowRef
$cpred :: WindowRef -> WindowRef
succ :: WindowRef -> WindowRef
$csucc :: WindowRef -> WindowRef
Enum, Int -> WindowRef -> ShowS
[WindowRef] -> ShowS
WindowRef -> String
(Int -> WindowRef -> ShowS)
-> (WindowRef -> String)
-> ([WindowRef] -> ShowS)
-> Show WindowRef
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [WindowRef] -> ShowS
$cshowList :: [WindowRef] -> ShowS
show :: WindowRef -> String
$cshow :: WindowRef -> String
showsPrec :: Int -> WindowRef -> ShowS
$cshowsPrec :: Int -> WindowRef -> ShowS
Show, Typeable, Get WindowRef
[WindowRef] -> Put
WindowRef -> Put
(WindowRef -> Put)
-> Get WindowRef -> ([WindowRef] -> Put) -> Binary WindowRef
forall t. (t -> Put) -> Get t -> ([t] -> Put) -> Binary t
putList :: [WindowRef] -> Put
$cputList :: [WindowRef] -> Put
get :: Get WindowRef
$cget :: Get WindowRef
put :: WindowRef -> Put
$cput :: WindowRef -> Put
Binary)

instance Default WindowRef where def :: WindowRef
def = Int -> WindowRef
WindowRef (-Int
1)