Skip to content

Commit

Permalink
updated/added examples used for a blog article
Browse files Browse the repository at this point in the history
  • Loading branch information
Ingo60 committed Oct 4, 2013
1 parent 7a9ae32 commit 07676b3
Show file tree
Hide file tree
Showing 3 changed files with 18 additions and 7 deletions.
10 changes: 10 additions & 0 deletions examples/ForH.fr
@@ -0,0 +1,10 @@
module examples.ForH where

import Data.List

main _ = print $ take 10 pyth
where
pyth = [ (x, y, m*m+n*n) |
m <- [2..], n <- [1..m-1],
let { x = m*m-n*n; y = 2*m*n }
]
13 changes: 7 additions & 6 deletions examples/Fpidigits.fr
Expand Up @@ -143,7 +143,7 @@ class Transformation {
-- import frege.lib.ForkJoin


data F = !F {q :: Integer, r :: Integer, s :: Integer, t :: Integer}
data F = F {!q :: Integer, !r :: Integer, !s :: Integer, !t :: Integer}

main [] = main ["1000"]
main (arg:_)
Expand All @@ -168,20 +168,21 @@ main (arg:_)
where nxt = next z k


f0 = F 1n 0n 0n 1n
f0 = F 1 0 0 1

fi :: Int -> F
fi n = let k = n.big in F k (4n*k+2n) 0n (2n*k+1n)
fi n = let k = n.big in F k (4*k+2) 0 (2*k+1)

flr x (F q r s t) = (q*x + r) `quot` (s*x + t)
comp1 (F q r s t) (F u v w x) = F (q*u+r*w) (q*v+r*x) (t*w) (t*x)
comp2 (F q r s t) (F u v w x) = F (q*u) (q*v+r*x) (s*u) (s*v+t*x)


next z !n
| y == flr 4n z = let
!f = F 10n ((-10n)*y) 0n 1n
| y == flr 4 z = let
!f = F 10 ((-10)*y) 0 1
!cfz = comp1 f z
in (y.int; cfz; n)
| otherwise = next (comp2 z (fi n)) (n+1)
where
y = flr 3n z
y = flr 3 z
2 changes: 1 addition & 1 deletion examples/ReverseStdin.fr
@@ -1,9 +1,9 @@
--- Reverse the standard input
module examples.ReverseStdin where


main _ = loop [] (repeat stdin.read) >>= mapM_ stdout.write

loop :: (Applicative α, Bind α) => [Int] -> [α Int] -> α [Int]
loop acc (a:as) = do
i <- a
if i < 0 then return acc -- end of file
Expand Down

0 comments on commit 07676b3

Please sign in to comment.