Skip to content

Instantly share code, notes, and snippets.

View christiaanb's full-sized avatar

Christiaan Baaij christiaanb

  • QBayLogic
  • Enschede, The Netherlands
View GitHub Profile
{-# LANGUAGE ScopedTypeVariables #-}
module BitPalindrome where
import CLaSH.Prelude
-- Not used anywhere, but using (!) is more idiomatic than "slice x x"
sl8 :: BitVector 8 -> (Bit, Bit, Bit, Bit, Bit, Bit, Bit, Bit)
sl8 a = (a ! 0, a ! 1, a ! 2, a ! 3, a ! 4, a ! 5, a ! 6, a ! 7)
, { "BlackBox" :
{ "name" : "CLaSH.Sized.Vector.fold"
, "type" : "fold :: (a -> a -> a) -> Vec (n+1) a -> a"
, "comment" : "THIS ONLY WORKS FOR POWER OF TWO LENGTH VECTORS"
, "templateD" :
"-- fold begin
fold_~SYM[0] : block
function pow2Index (d,n : in natural) return natural is
begin
return (2 ** d - 2 ** n);
module CPUD where
import CLaSH.Prelude
import qualified Data.List as L
type InstrAddr = Unsigned 8
type MemAddr = Unsigned 5
type Value = Signed 8
module Test.Delayed
where
import CLaSH.Prelude
import CLaSH.Prelude.Explicit
import Data.Functor
import Clocks
import Delayed
import Data.List
indices [] ix2 = ix2
indices ix1 [] = ix1
indices ((l1,r1):ix1) ((l2,r2):ix2)
| r1 < r2 = (l1,r1) : indices ix1 ((r1+1,r2):ix2)
| r1 == r2 = (l1,r1) : indices ix1 ix2
| r1 > r2 = (l2,r2) : indices ((r2+1,r1):ix1) ix2
{-# LANGUAGE Arrows, GADTs, TypeFamilies, NoImplicitPrelude, RankNTypes #-}
module ArrTest where
import Unsafe.Coerce
import CLaSH.Prelude hiding (id,(.))
import Control.Arrow
import Control.Category
import Data.Proxy
type family En a
module CLaSH.Signal.Enabled.SCase where
import Data.Default
import Language.Haskell.TH
scase e = do
e' <- e
case e' of
CaseE e2 ms -> do
nm1 <- newName "eb"
{-# LANGUAGE DeriveFunctor, DeriveFoldable, DeriveTraversable #-}
{-# OPTIONS_GHC -fno-full-laziness #-}
module Main where
import Bound
import Bound.Name
import Bound.Var
import Control.Applicative
import Control.Comonad
import Control.Monad
@christiaanb
christiaanb / DepLamInfer.hs
Last active August 29, 2015 14:03
Type Inference for a small dependently typed language
{-# LANGUAGE DeriveFunctor, DeriveFoldable, DeriveTraversable,
ScopedTypeVariables #-}
{- |
Usage:
>>> inferType1 (const undefined) dollar
>>> inferType2 (const undefined) dollar
>>> inferType3 (const undefined) dollar
>>> inferType4 (const undefined) id dollar
-}
module DepLamInfer where
/opt/ghc/7.8.3$ make
cd ./src/ghc-7.8.3 && ./configure --prefix=/opt/ghc/7.8.3 && make install
checking for path to top of build tree... /opt/ghc/7.8.3/src/ghc-7.8.3
Build platform inferred as: x86_64-apple-darwin
Host platform inferred as: x86_64-apple-darwin
Target platform inferred as: x86_64-apple-darwin
GHC build : x86_64-apple-darwin
GHC host : x86_64-apple-darwin
GHC target : x86_64-apple-darwin
checking for perl... /usr/bin/perl