-- | -- Module : Languages.UniquenessPeriods.Vector.ConstraintsG.Encoded -- Copyright : (c) OleksandrZhabenko 2020 -- License : MIT -- Stability : Experimental -- Maintainer : olexandr543@yahoo.com -- -- Provides a way to encode the needed constraint with possibly less symbols. -- {-# LANGUAGE FlexibleInstances #-} module Languages.UniquenessPeriods.Vector.ConstraintsG.Encoded where import Data.Monoid (mappend) import Text.Read (readMaybe) import Data.Maybe import qualified Data.Vector as VB import Data.List (intercalate,sort,nub) import Languages.UniquenessPeriods.Vector.ConstraintsG data EncodedContraints a b = E a | T a a a | SA a b | SB a b | F a a deriving (Eq, Ord) -- | Inspired by the: https://hackage.haskell.org/package/base-4.14.0.0/docs/Data-Maybe.html readMaybeEC :: String -> Maybe EncodedCnstrs readMaybeEC xs | null xs = Just (E 0) | otherwise = let (h,ts) = splitAt 1 xs in case h of "E" -> Just (E (fromMaybe 0 (readMaybe (take 1 . tail $ xs)::Maybe Int))) "F" -> let (y,z) = (readMaybe (take 1 ts)::Maybe Int, readMaybe (take 1 . drop 1 $ ts)) in case (y,z) of (Nothing,r2) -> Nothing (r1,Nothing) -> Nothing ~(Just x1, Just x2) -> if x1 < 7 && x2 < 7 then Just (F x1 x2) else Nothing "T" -> let (y,z,u) = (readMaybe (take 1 ts)::Maybe Int, readMaybe (take 1 . drop 1 $ ts)::Maybe Int, readMaybe (take 1 . drop 2 $ ts)::Maybe Int) in case (y,z,u) of (Nothing,r2,r3) -> Nothing (r1,Nothing,r3) -> Nothing (r1,r2,Nothing) -> Nothing ~(Just x1, Just x2, Just x3) -> if x1 < 7 && x2 < 7 && x3 < 7 then Just (T x1 x2 x3) else Nothing "A" -> let (y,zs) = (readMaybe (take 1 ts)::Maybe Int, filter (< 7) . catMaybes . map (\t -> readMaybe [t]::Maybe Int) . drop 1 $ ts) in case (y,zs) of (Nothing,r2) -> Nothing (_,[]) -> Nothing ~(Just x1, x2) -> if x1 < 7 then Just (SA x1 (VB.fromList x2)) else Nothing "B" -> let (y,zs) = (readMaybe (take 1 ts)::Maybe Int, filter (< 7) . catMaybes . map (\t -> readMaybe [t]::Maybe Int) . drop 1 $ ts) in case (y,zs) of (Nothing,r2) -> Nothing (_,[]) -> Nothing ~(Just x1, x2) -> if x1 < 7 then Just (SB x1 (VB.fromList x2)) else Nothing _ -> Nothing type EncodedCnstrs = EncodedContraints Int (VB.Vector Int) -- | Must be applied to the correct vector of permutation indeces. Otherwise, it gives runtime error (exception). decodeConstraint1 :: EncodedCnstrs -> VB.Vector (VB.Vector Int) -> VB.Vector (VB.Vector Int) decodeConstraint1 (E _) = id decodeConstraint1 (T i j k) = unsafeTriples i j k decodeConstraint1 (SA i v) = unsafeSeveralA i v decodeConstraint1 (SB i v) = unsafeSeveralB i v decodeConstraint1 (F i j) = filterOrderIJ i j decodeLConstraints :: [EncodedCnstrs] -> VB.Vector (VB.Vector Int) -> VB.Vector (VB.Vector Int) decodeLConstraints (x:xs) v = decodeLConstraints ys . decodeConstraint1 y $ v where (y:ys) = sort (x:xs) decodeLConstraints [] v = v getIEl :: EncodedCnstrs -> Int getIEl (E i) = i getIEl (T i _ _) = i getIEl (SA i _) = i getIEl (SB i _) = i getIEl (F i _) = i setIEl :: Int -> EncodedCnstrs -> EncodedCnstrs setIEl i (E _) = E i setIEl i (T _ j k) = T i j k setIEl i (SA _ v) = SA i v setIEl i (SB _ v) = SB i v setIEl i (F _ j) = F i j