Răsfoiți Sursa

[Haskell][26] Adding Solution

Vinicius Teshima 4 luni în urmă
părinte
comite
e244384a42
2 a modificat fișierele cu 93 adăugiri și 0 ștergeri
  1. 51 0
      haskell/src/0026.hs
  2. 42 0
      haskell/src/Utils.hs

+ 51 - 0
haskell/src/0026.hs

@@ -0,0 +1,51 @@
+
+import Utils
+
+import Data.Char
+import Data.List
+import Data.Ratio
+import Data.Maybe
+
+--import Debug.Trace
+--import Text.Printf
+
+f :: Int -> Int
+f 1 = 0
+f x = go' "" s s
+  where
+    s :: String
+    s = dropWhile (=='0') (drop 2 (longDiv (1%x)))
+    sL :: Int
+    sL = length s
+
+    go' :: String -> String -> String -> Int
+    --go' r (h:tl) sC | trace (printf "go' r=%s h=%c tl=%s sC=%s" r h tl sC) False = undefined
+    go' _ _  [] = 0
+    go' r [] sC  = go' "" (drop 1 sC) (drop 1 sC)
+    go' r sS sC | (length r) > (div (length sS) 2)= go' "" (drop 1 sC) (drop 1 sC)
+    go' r (h:tl) sC = if ((take 1 nR) == (take 1 tl)) && does_repeat nR tl -- does_repeat c 0 tl
+                      then (length r)+1
+                      else go' nR tl sC
+      where nR = (r++[h])
+
+    does_repeat :: String -> String -> Bool
+    --does_repeat n h | trace (printf "does_repeat n=%s h=%s" n h) False = undefined
+    does_repeat n [] = True
+    does_repeat n h = if (nS == hSlc)
+                      then does_repeat n (drop hSlcL h)
+                      else False
+      where nL = length n
+            hL = length h
+            hSlc = take nL h
+            hSlcL = length hSlc
+            nS = if hSlcL /= nL then take hSlcL n else n
+
+solution :: Int
+solution = l !! mI
+  where l = [1..1000]
+        fL = map f l
+        m = maximum fL
+        mI = fromJust (elemIndex m fL)
+
+main :: IO ()
+main = putStrLn ("Solution: " ++ show solution)

+ 42 - 0
haskell/src/Utils.hs

@@ -1,6 +1,7 @@
 module Utils where
   import Data.Function
   import Data.Maybe
+  import Data.Ratio
   import Data.List
   import Data.Char
 
@@ -241,3 +242,44 @@ module Utils where
       go' :: Show a => [a] -> Int -> Bool
       go' []     _ = False
       go' (x:xs) i = trace (printf "%5d -> %s" i (show x)) (go' xs (i+1))
+
+  slice :: Int -> Int -> [a] -> [a]
+  slice b s l = drop b l |> take s
+
+  howManyFit :: Int -> Int -> Int
+  --howManyFit x y | trace (printf "howManyFit %3d %3d" x y) False = undefined
+  howManyFit x y = if w == 0
+                   then 1
+                   else (if w > 0
+                         then 1 + (howManyFit x w)
+                         else 0)
+    where w = y-x
+
+  tW f (x:xs) = case f x of
+                  True -> tW f xs
+                  False -> x
+
+  longDiv :: Ratio Int -> String
+  longDiv r = if dn == nmRaw then "1" else pred ++ (go' nm False 5000)
+    where
+      nmRaw = numerator r
+      dn = denominator r
+      hMInc = iterate (+1) 1 |> tW (\x -> (howManyFit dn (nmRaw*(10^x))) == 0)
+      nm = nmRaw * (10^hMInc)
+      pred = case hMInc of
+               1 -> "0."
+               2 -> "0.0"
+               3 -> "0.00"
+               4 -> "0.000"
+               _ -> ""
+
+      go' :: Int -> Bool -> Int -> [Char]
+      go' 0 _ _ = []
+      go' _ _ 0 = []
+      go' x z n
+        -- | trace (printf "go' %3d %3d | hmf -> %3d" x n hmf) False = undefined
+        | hmf == 0 && z = ['0'] ++ (go' x False (n-1))
+        | otherwise = if hmf == 0
+                      then go' (x * 10) True (n)
+                      else [(intToDigit hmf)] ++ (go' (x-(dn*hmf)) False (n-1))
+                        where hmf = howManyFit dn x