Skip to content

Instantly share code, notes, and snippets.

@Ino4137
Created October 17, 2018 18:03
Show Gist options
  • Select an option

  • Save Ino4137/892bd6a773592a9b730dd1871528adb2 to your computer and use it in GitHub Desktop.

Select an option

Save Ino4137/892bd6a773592a9b730dd1871528adb2 to your computer and use it in GitHub Desktop.
Plotter - simple function plotting
{-# LANGUAGE DeriveTraversable, GADTs #-}
import Data.List (intersperse,intercalate,transpose)
import Text.Printf (printf)
type Graph = GraphF Bool
type Function = Integer -> Integer -> Bool
height, width :: Integer
height = 40
width = 60
uni, diff :: Function -> Function -> Function
uni f g = \x y -> f x y || g x y
diff f g = \x y -> f x y && not (g x y)
mrAnts, four, foour, foo5 :: Function
four x y = x == 4
foour x y = y == 4
foo5 x y = y^2 + x^2 <= 100
mrAnts = (\x y -> x^2 <= y) `uni` (\x y -> (round . negate $ (1/4 * (fromIntegral x)^2)) + 9 == y)
render :: Bool -> Char
render True = '#'
render False = toEnum 183
newtype GraphF a = Graph {unGraph :: [[a]]} deriving (Eq,Functor)
instance (a ~ Bool) => Show (GraphF a) where
show = ("\n "++) . intersperse ' ' . intercalate "\n"
. (++(map (printf ('%' : show (width + 4) ++ "s") :: String -> String) . transpose . map (printf "%3d") $ range width))
. map (uncurry (++)) . zip (reverse . map (printf "%3d") $ range height) . unGraph . fmap render
range :: Integral a => a -> [a]
range p = [negate (p`div`2)..(p`div`2)]
genGraph :: Integral a => a -> a -> GraphF (a,a)
genGraph width height = Graph . flip map (reverse $ range height) . traverse (,) $ range width
plot :: Function -> Graph
plot f = fmap (uncurry f) (genGraph width height)
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment