module Music.Theory.Array.Cell_Ref where
import Data.Char
import Data.Function
import Data.Maybe
import qualified Data.Array as A
newtype Column_Ref = Column_Ref {Column_Ref -> String
column_ref_string :: String}
instance Read Column_Ref where readsPrec :: Row_Ref -> ReadS Column_Ref
readsPrec Row_Ref
_ String
s = [(String -> Column_Ref
Column_Ref String
s,[])]
instance Show Column_Ref where show :: Column_Ref -> String
show = Column_Ref -> String
column_ref_string
instance Eq Column_Ref where == :: Column_Ref -> Column_Ref -> Bool
(==) = forall a. Eq a => a -> a -> Bool
(==) forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
`on` Column_Ref -> Row_Ref
column_index
instance Ord Column_Ref where compare :: Column_Ref -> Column_Ref -> Ordering
compare = forall a. Ord a => a -> a -> Ordering
compare forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
`on` Column_Ref -> Row_Ref
column_index
instance Enum Column_Ref where
fromEnum :: Column_Ref -> Row_Ref
fromEnum = Column_Ref -> Row_Ref
column_index
toEnum :: Row_Ref -> Column_Ref
toEnum = Row_Ref -> Column_Ref
column_ref
instance A.Ix Column_Ref where
range :: (Column_Ref, Column_Ref) -> [Column_Ref]
range = (Column_Ref, Column_Ref) -> [Column_Ref]
column_range
index :: (Column_Ref, Column_Ref) -> Column_Ref -> Row_Ref
index = (Column_Ref, Column_Ref) -> Column_Ref -> Row_Ref
interior_column_index
inRange :: (Column_Ref, Column_Ref) -> Column_Ref -> Bool
inRange = (Column_Ref, Column_Ref) -> Column_Ref -> Bool
column_in_range
rangeSize :: (Column_Ref, Column_Ref) -> Row_Ref
rangeSize = (Column_Ref, Column_Ref) -> Row_Ref
column_range_size
type Column_Range = (Column_Ref,Column_Ref)
type Row_Ref = Int
row_index :: Row_Ref -> Int
row_index :: Row_Ref -> Row_Ref
row_index Row_Ref
r = Row_Ref
r forall a. Num a => a -> a -> a
- Row_Ref
1
type Row_Range = (Row_Ref,Row_Ref)
type Cell_Ref = (Column_Ref,Row_Ref)
type Cell_Range = (Cell_Ref,Cell_Ref)
letter_index :: Char -> Int
letter_index :: Char -> Row_Ref
letter_index Char
c = forall a. Enum a => a -> Row_Ref
fromEnum (Char -> Char
toUpper Char
c) forall a. Num a => a -> a -> a
- forall a. Enum a => a -> Row_Ref
fromEnum Char
'A'
index_letter :: Int -> Char
index_letter :: Row_Ref -> Char
index_letter Row_Ref
i = forall a. Enum a => Row_Ref -> a
toEnum (Row_Ref
i forall a. Num a => a -> a -> a
+ forall a. Enum a => a -> Row_Ref
fromEnum Char
'A')
column_index :: Column_Ref -> Int
column_index :: Column_Ref -> Row_Ref
column_index (Column_Ref String
c) =
let m :: [Row_Ref]
m = forall a. (a -> a) -> a -> [a]
iterate (forall a. Num a => a -> a -> a
* Row_Ref
26) Row_Ref
1
i :: [Row_Ref]
i = forall a. [a] -> [a]
reverse (forall a b. (a -> b) -> [a] -> [b]
map Char -> Row_Ref
letter_index String
c)
in forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum (forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith forall a. Num a => a -> a -> a
(*) [Row_Ref]
m (forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith forall a. Num a => a -> a -> a
(+) [Row_Ref
0..] [Row_Ref]
i))
interior_column_index :: Column_Range -> Column_Ref -> Int
interior_column_index :: (Column_Ref, Column_Ref) -> Column_Ref -> Row_Ref
interior_column_index (Column_Ref
l,Column_Ref
r) Column_Ref
c =
let n :: Row_Ref
n = Column_Ref -> Row_Ref
column_index Column_Ref
c
l' :: Row_Ref
l' = Column_Ref -> Row_Ref
column_index Column_Ref
l
r' :: Row_Ref
r' = Column_Ref -> Row_Ref
column_index Column_Ref
r
in if Row_Ref
n forall a. Ord a => a -> a -> Bool
> Row_Ref
r'
then forall a. HasCallStack => String -> a
error (forall a. Show a => a -> String
show (String
"interior_column_index",Column_Ref
l,Column_Ref
r,Column_Ref
c))
else Row_Ref
n forall a. Num a => a -> a -> a
- Row_Ref
l'
column_ref :: Int -> Column_Ref
column_ref :: Row_Ref -> Column_Ref
column_ref =
let rec :: Row_Ref -> String
rec Row_Ref
n = case Row_Ref
n forall a. Integral a => a -> a -> (a, a)
`quotRem` Row_Ref
26 of
(Row_Ref
0,Row_Ref
r) -> [Row_Ref -> Char
index_letter Row_Ref
r]
(Row_Ref
q,Row_Ref
r) -> Row_Ref -> Char
index_letter (Row_Ref
q forall a. Num a => a -> a -> a
- Row_Ref
1) forall a. a -> [a] -> [a]
: Row_Ref -> String
rec Row_Ref
r
in String -> Column_Ref
Column_Ref forall b c a. (b -> c) -> (a -> b) -> a -> c
. Row_Ref -> String
rec
column_ref_pred :: Column_Ref -> Column_Ref
column_ref_pred :: Column_Ref -> Column_Ref
column_ref_pred = forall a. Enum a => a -> a
pred
column_ref_succ :: Column_Ref -> Column_Ref
column_ref_succ :: Column_Ref -> Column_Ref
column_ref_succ = forall a. Enum a => a -> a
succ
column_indices :: Column_Range -> (Int,Int)
column_indices :: (Column_Ref, Column_Ref) -> (Row_Ref, Row_Ref)
column_indices =
let bimap :: (t -> b) -> (t, t) -> (b, b)
bimap t -> b
f (t
i,t
j) = (t -> b
f t
i,t -> b
f t
j)
in forall {t} {b}. (t -> b) -> (t, t) -> (b, b)
bimap Column_Ref -> Row_Ref
column_index
column_range :: Column_Range -> [Column_Ref]
column_range :: (Column_Ref, Column_Ref) -> [Column_Ref]
column_range (Column_Ref, Column_Ref)
rng =
let (Row_Ref
l,Row_Ref
r) = (Column_Ref, Column_Ref) -> (Row_Ref, Row_Ref)
column_indices (Column_Ref, Column_Ref)
rng
in forall a b. (a -> b) -> [a] -> [b]
map Row_Ref -> Column_Ref
column_ref [Row_Ref
l .. Row_Ref
r]
column_in_range :: Column_Range -> Column_Ref -> Bool
column_in_range :: (Column_Ref, Column_Ref) -> Column_Ref -> Bool
column_in_range (Column_Ref, Column_Ref)
rng Column_Ref
c =
let (Row_Ref
l,Row_Ref
r) = (Column_Ref, Column_Ref) -> (Row_Ref, Row_Ref)
column_indices (Column_Ref, Column_Ref)
rng
k :: Row_Ref
k = Column_Ref -> Row_Ref
column_index Column_Ref
c
in Row_Ref
k forall a. Ord a => a -> a -> Bool
>= Row_Ref
l Bool -> Bool -> Bool
&& Row_Ref
k forall a. Ord a => a -> a -> Bool
<= Row_Ref
r
column_range_size :: Column_Range -> Int
column_range_size :: (Column_Ref, Column_Ref) -> Row_Ref
column_range_size = (forall a. Num a => a -> a -> a
+ Row_Ref
1) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Num a => a -> a
negate forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry (-) forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Column_Ref, Column_Ref) -> (Row_Ref, Row_Ref)
column_indices
row_range :: Row_Range -> [Row_Ref]
row_range :: (Row_Ref, Row_Ref) -> [Row_Ref]
row_range = forall a. Ix a => (a, a) -> [a]
A.range
cell_ref_minima :: Cell_Ref
cell_ref_minima :: Cell_Ref
cell_ref_minima = (String -> Column_Ref
Column_Ref String
"A",Row_Ref
1)
parse_cell_ref :: String -> Maybe Cell_Ref
parse_cell_ref :: String -> Maybe Cell_Ref
parse_cell_ref String
s =
case forall a. (a -> Bool) -> [a] -> ([a], [a])
span Char -> Bool
isUpper String
s of
([],String
_) -> forall a. Maybe a
Nothing
(String
c,String
r) -> case forall a. (a -> Bool) -> [a] -> ([a], [a])
span Char -> Bool
isDigit String
r of
(String
n,[]) -> forall a. a -> Maybe a
Just (String -> Column_Ref
Column_Ref String
c,forall a. Read a => String -> a
read String
n)
(String, String)
_ -> forall a. Maybe a
Nothing
is_cell_ref :: String -> Bool
is_cell_ref :: String -> Bool
is_cell_ref = forall a. Maybe a -> Bool
isJust forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Maybe Cell_Ref
parse_cell_ref
parse_cell_ref_err :: String -> Cell_Ref
parse_cell_ref_err :: String -> Cell_Ref
parse_cell_ref_err = forall a. a -> Maybe a -> a
fromMaybe (forall a. HasCallStack => String -> a
error String
"parse_cell_ref") forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Maybe Cell_Ref
parse_cell_ref
cell_ref_pp :: Cell_Ref -> String
cell_ref_pp :: Cell_Ref -> String
cell_ref_pp (Column_Ref String
c,Row_Ref
r) = String
c forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show Row_Ref
r
cell_index :: Cell_Ref -> (Int,Int)
cell_index :: Cell_Ref -> (Row_Ref, Row_Ref)
cell_index (Column_Ref
c,Row_Ref
r) = (Column_Ref -> Row_Ref
column_index Column_Ref
c,Row_Ref -> Row_Ref
row_index Row_Ref
r)
index_to_cell :: (Int,Int) -> Cell_Ref
index_to_cell :: (Row_Ref, Row_Ref) -> Cell_Ref
index_to_cell (Row_Ref
c,Row_Ref
r) = (Row_Ref -> Column_Ref
column_ref Row_Ref
c,Row_Ref
r forall a. Num a => a -> a -> a
+ Row_Ref
1)
parse_cell_index :: String -> (Int,Int)
parse_cell_index :: String -> (Row_Ref, Row_Ref)
parse_cell_index = Cell_Ref -> (Row_Ref, Row_Ref)
cell_index forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Cell_Ref
parse_cell_ref_err
cell_range :: Cell_Range -> [Cell_Ref]
cell_range :: Cell_Range -> [Cell_Ref]
cell_range ((Column_Ref
c1,Row_Ref
r1),(Column_Ref
c2,Row_Ref
r2)) =
[(Column_Ref
c,Row_Ref
r) |
Column_Ref
c <- (Column_Ref, Column_Ref) -> [Column_Ref]
column_range (Column_Ref
c1,Column_Ref
c2)
,Row_Ref
r <- (Row_Ref, Row_Ref) -> [Row_Ref]
row_range (Row_Ref
r1,Row_Ref
r2)]
cell_range_row_order :: Cell_Range -> [Cell_Ref]
cell_range_row_order :: Cell_Range -> [Cell_Ref]
cell_range_row_order ((Column_Ref
c1,Row_Ref
r1),(Column_Ref
c2,Row_Ref
r2)) =
[(Column_Ref
c,Row_Ref
r) |
Row_Ref
r <- (Row_Ref, Row_Ref) -> [Row_Ref]
row_range (Row_Ref
r1,Row_Ref
r2)
,Column_Ref
c <- (Column_Ref, Column_Ref) -> [Column_Ref]
column_range (Column_Ref
c1,Column_Ref
c2)]