Skip to content

Instantly share code, notes, and snippets.

View JackTheEngineer's full-sized avatar

JackTheEngineer JackTheEngineer

View GitHub Profile
@JackTheEngineer
JackTheEngineer / HChartRender.hs
Last active March 29, 2020 23:16
Chart rendering code
-- | This function bridges gi-cairo with the hand-written cairo
-- package. It takes a `GI.Cairo.Context` (as it appears in gi-cairo),
-- and a `Render` action (as in the cairo lib), and renders the
-- `Render` action into the given context.
renderWithContext :: GI.Cairo.Context -> ReaderT Cairo IO a -> IO (a)
renderWithContext ct rendered = withManagedPtr ct $ \p -> runReaderT rendered (Cairo (castPtr p))
activateRender :: (Int, Int) -> (Channel, DrawingArea) -> IO ()
activateRender (width, height) (channel, cairoArea) = do
widgetSetSizeRequest cairoArea (fromIntegral width) (fromIntegral height)
@JackTheEngineer
JackTheEngineer / fileMirror.hs
Last active October 13, 2019 21:21
A haskell Program that watches ".txt" files in a given directory and prints out their names and timestamps, if latter has changed
{-# LANGUAGE OverloadedStrings #-}
import System.FSNotify
import System.Directory
import Control.Applicative((<$>))
import Control.Exception(throw)
import Control.Monad(when,forM_)
import System.FilePath ((</>))
import Development.Shake.FilePath (splitPath, splitDirectories)
import Control.Concurrent (threadDelay)
module Main where
import Graphics.Rendering.Chart.Easy
import Graphics.Rendering.Chart.Gtk
import qualified Graphics.UI.Gtk as G
import qualified Graphics.Rendering.Cairo as C
import qualified Graphics.UI.Gtk.Gdk.Events as GE
import Graphics.Rendering.Chart.Renderable
@JackTheEngineer
JackTheEngineer / SerialportExample.hs
Created June 27, 2018 11:57
Haskell Serial Port with "serialport" library
import qualified Data.ByteString.Char8 as B
import System.IO
import System.Hardware.Serialport
import Control.Monad.Loops
import Control.Monad
import Data.Char
stringToIntList :: String -> [Int]
stringToIntList line
| ((>2) . length) line = map ord line
@JackTheEngineer
JackTheEngineer / KnightPositioning.hs
Last active May 27, 2018 00:50
Monadic Computations with named parameters in functions
import Control.Monad
import Control.Applicative
import Data.List
type KnightPos = (Int, Int)
nextMoves c r = [(c+2,r-1), (c+2,r+1),(c-2,r-1),(c-2,r+1),
(c+1,r-2),(c+1,r+1),(c-1,r-2),(c-1,r+2)]
inField c r = (c `elem` [1..8] && r `elem` [1..8])
import Test.QuickCheck
import Data.List (intersperse)
split :: Char -> String -> [String]
split c [] = []
split c xs = xs' : if null xs'' then [] else split c (tail xs'')
where xs' = takeWhile (/=c) xs
xs''= dropWhile (/=c) xs
unsplit :: Char -> [String] -> String
@JackTheEngineer
JackTheEngineer / ScrolledFrame.py
Last active February 10, 2024 16:26
Tkinter python Scrolled Window / Frame / Canvas with Mousewheel support ( based upon EugeneBakin 's scrframe.py )
from tkinter import ttk
import tkinter as tk
import functools
fp = functools.partial
class VerticalScrolledFrame(ttk.Frame):
"""
A pure Tkinter scrollable frame that actually works!
* Use the 'interior' attribute to place widgets inside the scrollable frame
* Construct and pack/place/grid normally