module Konnakol.Diagrams where import Diagrams.Prelude hiding (P) import Diagrams.Backend.SVG.CmdLine import Data.List.Split ( chunksOf ) import Data.Colour.SRGB.Linear ( rgb ) import qualified Data.Data as Data.Typeable.Internal import Konnakol.Define ( calculateCount, genKorvai, getCountPerBeat, getMohraSeparation, getMohraSpeed, mohraC1, mohraC2, mohrad, thriputa, BeatCount(Laghu, Dhruta, Anudhruta), JatiGati(Chaturasra), JustNums(..), Thala(..), UIComp ) import Data.List import System.Random import Diagrams.TwoD (text) import qualified Control.Arrow as Data.Bifunctor -- | To convert a series of JustNums into a progression of numbers between 0 and 1 based on the length -- of the phrase/ gap sepToSingles::[JustNums] -> [Double] sepToSingles [] =[] sepToSingles (B : xs) = sepToSingles xs sepToSingles ((P a):xs) = map (\x -> fromIntegral x/fromIntegral a) [1..a] ++ sepToSingles xs sepToSingles ((G a):xs) = map (\x -> fromIntegral (-x + 1)/ fromIntegral a) [1..a] ++ sepToSingles xs -- | Splitting a set of numbers into subsets based on the length of avarta toColors::[JustNums] -> Int -> [[Double]] toColors xs n = chunksOf n $ sepToSingles xs -- | Core function to visualize a list of JustNums visNums:: [JustNums] -> JatiGati-> Thala ->JatiGati-> Int -> Diagram B visNums arr jati thala gati sp = let c = getCountPerBeat gati sp avarta = c * calculateCount jati thala in gridKon (toColors arr avarta) (getLabels thala jati c) -- | Core function to generate a picture a Korvai pictureKorvai :: JatiGati -> Thala -> JatiGati -> StdGen ->Diagram B pictureKorvai jati thala gati gen = let (_,korvai) = genKorvai jati thala gati gen sp = getMohraSpeed gati -1 avarta = calculateCount jati thala*getCountPerBeat gati sp counts = if avarta < 50 then 4* avarta else avarta overallCount = 2* counts colors = toColors korvai avarta in gridKon colors (getLabels thala jati (getCountPerBeat gati sp)) -- | Function to create squares for Korvai based on value generated by sepToSingles getSquares::Double -> Diagram B getSquares x = if x >0 then rect 1 1 # lw thin # fc (rgb 1 x x) else rect 1 1 # lw thin # fc (rgb 0 (1+x) (1+x)) -- | Core function to draw the grid for the Korvai gridKon :: [[Double]] -> String ->Diagram B gridKon x s = lattice where y = length x labels = gridThala s grids = map (centerXY.hcat. map getSquares) x lattice = vcat [labels, vcat grids] -- | Function to split components of Mohra to a a series of values between 0 and 1 along with their types sepToSinglesM::(Int, Int) -> [(Double, Int)] sepToSinglesM (a,y) = map (\x -> (fromIntegral x/fromIntegral a,y) ) [1..a] -- | Core function to picture a Mohra for a given jati, thala and gati pictureMohra :: JatiGati -> Thala -> JatiGati -> Diagram B pictureMohra jati thala gati = let sp = getMohraSpeed gati phd = mohrad gati overAllCount = if calculateCount jati thala<= 4 then 2*calculateCount jati thala else calculateCount jati thala [a,b,c,d] = getMohraSeparation (getCountPerBeat gati sp*overAllCount) gati lenC1 = length $ mohraC1 gati lenC2 = length (mohraC2 gati) - getCountPerBeat gati sp mohraRep = concatMap sepToSinglesM ([(a, 1), (b, 2), (c,3), (d, 4), (a, 1), (b, 2), (c, 3), (d, 4), (a, 1), (b, 2), (c, 3), (lenC1, 5), (a, 1), (lenC1, 5), (a, 1), (lenC2, 5)]::[(Int,Int)]) avarta = getCountPerBeat gati sp * calculateCount jati thala colors = chunksOf avarta mohraRep in gridKonM colors (getLabels thala jati (getCountPerBeat gati sp)) -- | Function to obtain equivalent symbols for representation of a thala on top of the grid getLabels::Thala->JatiGati->Int->String getLabels (T []) _ _ = "" getLabels (T (Laghu:xs)) jati cPB = (show Laghu ++ replicate (cPB - 1) ' ') ++ concat (replicate (fromEnum jati - 1) ('^': replicate (cPB -1) ' ' )) ++ getLabels (T xs) jati cPB getLabels (T (Dhruta:xs)) jati cPB = (show Dhruta ++ replicate (cPB - 1) ' ') ++ '^': replicate (cPB-1) ' '++ getLabels (T xs) jati cPB getLabels (T (Anudhruta:xs)) jati cPB = (show Anudhruta ++ replicate (cPB - 1) ' ') ++ getLabels (T xs) jati cPB -- | Function to draw squares for each individual block in a Mohra based on the type getSquaresM::(Double, Int) -> Diagram B getSquaresM (x, 1) = rect 1 1 # lw thin # fc (rgb x 1 x) getSquaresM (x, 2) = rect 1 1 # lw thin # fc (rgb x 0 x) getSquaresM (x, 3) = rect 1 1 # lw thin # fc (rgb x x 1) getSquaresM (x, 4) = rect 1 1 # lw thin # fc (rgb x x 0) getSquaresM (x, 5) = rect 1 1 # lw thin # fc (rgb 1 x x) gridThala::String ->Diagram B gridThala = centerXY.hcat.map (\c->text [c] <> rect 1 1 #lw none ) -- | Function to draw the lattice for Mohra gridKonM :: [[(Double, Int)]] ->String-> Diagram B gridKonM x s = lattice where y = length x labels = gridThala s grids = map (centerXY.hcat. map getSquaresM) x lattice = vcat [labels, vcat grids] -- | To create a sector with the size based on the element's index and the total array size createSector :: Double->Double->Double-> Diagram B createSector val ind n = annularWedge 1 0.6 d a # fc col where d :: Direction V2 Double d = rotateBy (ind/n) xDir a :: Angle Double a = (2*pi/n) @@ rad col = getCols val -- | To convert the given set of values to the circular diagram getSectors :: [Double] -> Diagram B getSectors x = lattice where lattice = mconcat $ map (\i -> createSector (x!!i) (fromIntegral i) (fromIntegral (length x))) [0,1..(length x - 1)] -- | To take a given list of JustNums and to obtain the circular diagram compToCircle :: [JustNums] -> JatiGati-> Thala ->JatiGati-> Int -> Diagram B compToCircle arr jati thala gati sp = let c = getCountPerBeat gati sp avarta = c * calculateCount jati thala in getSectors (toColors' arr avarta) -- | To visualize the Korvai as a circle instead of grids pictureKorvaiC :: JatiGati -> Thala -> JatiGati -> StdGen ->Diagram B pictureKorvaiC jati thala gati gen = let (_,korvai) = genKorvai jati thala gati gen sp = getMohraSpeed gati -1 avarta = calculateCount jati thala*getCountPerBeat gati sp counts = if avarta < 50 then 4* avarta else avarta overallCount = 2* counts colors = toColors' korvai avarta in getSectors colors -- | Splitting a set of numbers into subsets based on the length of avarta and summing the subsets toColors'::[JustNums] -> Int -> [Double] toColors' xs n = map sum . transpose $ chunksOf n (sepToSingles' xs (length xs)) -- | To convert a series of JustNums into a progression of numbers between 0 and 1 based on the length -- of the phrase/ gap for circular visualization sepToSingles'::[JustNums]->Int -> [Double] sepToSingles' [] n =[] sepToSingles' (B : xs) n = sepToSingles' xs n sepToSingles' ((P a):xs) n = map (\x -> fromIntegral x/fromIntegral n) [1..a] ++ sepToSingles' xs n sepToSingles' ((G a):xs) n = map (\x -> fromIntegral (-x + 1)/ fromIntegral n) [1..a] ++ sepToSingles' xs n -- | To obtain the for display in overlapping circles getCols :: (Ord a, Fractional a) => a -> Colour a getCols x = if x >0 then rgb (0.5 + x/2) x x else rgb (0.5 + x/2) (-x) (-x) newtype Varying = S [(Double , [JustNums])] convToChanging::Varying -> [(Double, Double)] convToChanging (S []) = [] convToChanging (S ((x,y):xs)) = map (\t -> (t, x)) (sepToSingles y) ++ convToChanging (S xs) getSquaresV:: (Double,Double) -> Diagram B getSquaresV (x,y) = if x >0 then rect y 1 # lw thin # fc (rgb 1 x x) else rect y 1 # lw thin # fc (rgb 0 (1+x) (1+x)) splitIt::[(Double,Double)] -> Double -> [(Double, Double)] -> Double -> [[(Double, Double)]] splitIt [] _ l _ = [l | l /= []] splitIt ((x,y):xs) a l c = if abs(a + y - c) < 0.000000001 then (l++ [(x,y)]) : splitIt xs 0 [] c else splitIt xs (a + y) (l ++ [(x,y)]) c -- | Core function to visualize a list of JustNums visNumsVarying:: Varying -> JatiGati-> Thala -> Diagram B visNumsVarying arr jati thala = lattice where vals = convToChanging arr maxm = maximum (map snd vals) vals2 = map (Data.Bifunctor.second (maxm /)) vals labels = gridThala (getLabels thala jati (floor maxm)) grids = map (centerXY.hcat. map getSquaresV) (splitIt vals2 0 [] (maxm*fromIntegral(calculateCount jati thala))) lattice = vcat [labels, vcat grids] main1 = mainWith $ pictureKorvai Chaturasra thriputa Chaturasra (mkStdGen 758) main = main2 main4 = mainWith $ pictureKorvaiC Chaturasra thriputa Chaturasra (mkStdGen 758) main3 = mainWith $pictureMohra Chaturasra thriputa Chaturasra main2 = mainWith $ visNumsVarying (S [(3,[P 4, G 2, P 4, G 2]),(4, [P 5, G 3, P 5, G 3]), (5, [ P 6, G 4, P 6, G 4]), (7, [P 9, G 5, P 9, G 5])]) Chaturasra thriputa