news

2005 2006 2007 2008 2009 2010 2011 2012 2013 2014 2015 2016 2017 2018 2019 2020 FOSS conference devops documentation emacs fedora foss freedom gnome haskell install laptop lisp photo ruby travel verilog vhdl vlsi workshop xmonad


netlist-to-vhdl converts a Netlist AST (Abstract Syntax Tree) to VHDL (VHSIC Hardware Description Language). It is now available in Fedora. Install it using:

 $ sudo yum install ghc-netlist-to-vhdl-devel

The genVHDL function accepts a Netlist.AST module and emits VHDL. For example:

{-# LANGUAGE ParallelListComp #-}

import Language.Netlist.AST
import Language.Netlist.Util
import Language.Netlist.GenVHDL

t :: Module
t = Module "foo" (f ins) (f outs) [] ds
  where
    f xs = [ (x, makeRange Down sz) | (x, sz) <- xs ]
    ins = [("clk", 1), ("reset", 1), ("enable", 1), ("x", 16)]
    outs = [("z", 16)]

ds :: [Decl]
ds = [ NetDecl "a" (makeRange Down 16) (Just (ExprVar "x"))
     , NetDecl "b" (makeRange Down 16) (Just (sizedInteger 16 10))
     , MemDecl "c" Nothing (makeRange Down 16) Nothing
     , ProcessDecl (Event (ExprVar "clk") PosEdge)
                   (Just (Event (ExprVar "reset") PosEdge, 
		   	(Assign (ExprVar "c") (sizedInteger 16 0))))
                   (If (ExprVar "enable")
                         (Assign (ExprVar "c") (ExprVar "x"))
                         Nothing)
     ]

main = do
        putStrLn $ genVHDL t ["work.all"]

The above code can be compiled and run using:

$ ghc --make Example.hs

$ ./Example

When executed it will generate the following VHDL:

library IEEE;
use IEEE.STD_LOGIC_1164.ALL;
use IEEE.NUMERIC_STD.ALL;
use work.all;
entity foo is
  port(clk : in std_logic;
       reset : in std_logic;
       enable : in std_logic;
       x : in std_logic_vector(15 downto 0);
       z : out std_logic_vector(15 downto 0));
end entity foo;
architecture str of foo is
  signal a : std_logic_vector(15 downto 0) := x;
  signal b : std_logic_vector(15 downto 0) := "0000000000001010";
  signal c : std_logic_vector(15 downto 0);
begin
  proc3 : process(clk,reset) is
  begin
    if reset = '1' then
      c <= "0000000000000000";
    elsif rising_edge(clk) then
      if enable then
        c <= x;
      end if;
    end if;
  end process proc3;
end architecture str;

sized-types provides indices, matrices, signed and unsigned bit vectors. It is now available in Fedora. Install it using:

 $ sudo yum install ghc-sized-types-devel

An n-bit sized type is represented by Xn. For example, a 4-bit unsigned number can be represented by Unsigned X4. Few examples:

ghci> [minBound .. maxBound] :: [X4]
[0,1,2,3]

ghci> 100 :: Unsigned X4
4

ghci> 100 + 100 :: Signed X8
-56

The signed and unsigned types can also be used in matrix operations:

ghci> let n = matrix [1..12] :: Matrix (X3,X4) Int
ghci> n
[ 1, 2, 3, 4, 5, 6, 7, 8, 9, 10, 11, 12 ]

ghci> print $ tranpose n
[ 1, 5, 9, 2, 6, 10, 3, 7, 11, 4, 8, 12 ]

ghci> let m = matrix [3,4,5,6] :: Matrix X4 Int
ghci> m
[ 3, 4, 5, 6]
ghci> m ! 2
5

These general purpose types are very useful in specifying hardware descriptions, especially when you need fixed-width, irregular size, signed and unsigned numbers.

I attended Barcamp Mumbai 9 at Veermata Jijabai Technological Institute (VJTI), Mumbai, Maharashtra, India on Sunday, June 17, 2012. After an informal introduction, four parallel tracks were scheduled. Each session was 20 minutes long, and 10 minutes between talks for people to move between the halls. Although most of the talks were non-technical, there were quite a few interesting sessions.

VJTI sign board

Raj Desai presented on “The Math of Music”. He explained how the rhythms or beats used in music formed a pattern, and how they often use prime numbers. For example, a 5-beat sequence is made from a combination of a 2-3 beat sequence, or, a 7-beat sequence is made from a 2-2-3 or a 3-2-2 beat sequence. He also played the different beats, giving numerous examples.

Krishna Patel played the short movie “Geri’s Game” in his session on “How To Watch a Movie”, and explained the different aspects in a movie like composition, props, sound, colour etc. He mentioned that one might have to watch a movie several times focusing on just one aspect at a time to observe and learn how they have been used.

List of talks

The session on “How to memorise a pack of 52 playing cards in under 2 minutes” by Aniceto Pereira taught how to use two simple mnemonic systems to memorise a pack of cards. For the four suites, we used the letters C (clubs), S (spades), H (hearts), D (diamonds). For each card in a suite, a consonant is assigned. For example, Ace was assigned the letter ’t’ or ‘d’, because there is one vertical line in it, referring to one. The number ‘2’ was assigned the letter ‘n’ because there were two downward strokes in it. So, if we had an Ace (’t’) of clubs (‘c’), we would combine the letter and the consonant to form an image, say “cat”, and associate it with our environment to remember it. For each card that we have, we build a series of images to remember them.

Anurag Patel’s session on “Sh*t people say to a chat bot” was hilarious! He had created http://rickfare.com to compute Mumbai’s autorickshaw fare calculation, and later added support for other cities as well. There were times when people started to chat with the bot, and he shared quite a few entertaining, priceless conversations from the server logs.

The talk on “Negotiating with VCs - An Entrepreneur’s Legal Guide” by Abhyudaya Agarwal was very informative, and detailed. I had presented “Quite Universal Circuit Simulator - A Qt Love Story”, an introduction to electrical circuit theory using Qucs. You can install Qucs on Fedora using:

  $ sudo yum install qucs

I also had a chance to stay at Anu Shakti Nagar, a quiet, serene, beautiful residential township in Mumbai in this visit. Few pictures taken during the trip are available in my /gallery.

A Fedora Activity Day (FAD) was organized on Saturday, June 2, 2012 at the Red Hat office premises in Pune, India.

Discussion in progress

This was an activity based event, where there were no talks. The various topics suggested during the FAD included development, packaging, and documentation work.

The newbies worked on GNU Hello RPM packaging, while others worked on pushing updates to existing packages, and packaging new software.

I had submitted a new Csmith package release for review, and packaged and submitted sized-types, and netlist-to-vhdl Haskell packages for review. Lakshmi Narasimhan completed the package review for sized-types.

I had requested Fedora Infrastructure to make Agilo for Trac (Apache license) available. It was made available for testing during the FAD, and I tested the same with the Fedora Electronic Lab trac instance. All the Agilo plugins are now enabled in the trac for use.

We also had an F17 release party during the event, where Rahul Sundaram cut a beautiful, tasty, F17 cake.

F17 cake

Thanks to Red Hat for hosting the event, sponsoring lunch, and providing the facilities for the FAD.

More photos are available in my /gallery.

We are happy to announce “I know what You Are Going To Do This Summer 2012”, a free (as in freedom), online (IRC-based) training program in Free/Libre/Open Source Software at #dgplug on irc.freenode.net.

If you are a prospective candidate, or a mentor, who would like to participate in this year’s sessions, please go through the previous year’s IRC logs.

We will have review, and Q&A sessions, on topics addressed in the previous years before proceeding with new topics for this year.

The session timings are usually after 1900 IST, every day.

To participate, you will need a reliable Internet connection, and any latest distribution installed (Fedora 16/17 preferable).

The program is open to all. If you are interested in participating, please confirm the same by sending an e-mail to kushaldas AT gmail DOT com, or shakthimaan at fedoraproject dot org.

References:

URL: http://dgplug.org

Planet: http://planet.dgplug.org

Wiki: http://wiki.dgplug.org

Mailing list group (for queries, discussions): http://lists.dgplug.org/listinfo.cgi/users-dgplug.org

Fort Jadhav Ghad
Welcome note
Museum side
Fort rear, side
swimming pool

More photos available in my /gallery.

A Fedora Activity Day event is scheduled for Saturday, June 2, 2012 at the Red Hat, Pune, India office premises.

Venue:

  Red Hat Software Services Pvt Ltd 
  Tower X, Level-1,
  Cybercity, Magarpatta City,
  Hadapsar, Pune 411 013
  Maharashtra
  India

Date : Saturday, June 2, 2012.

Time : 1000 IST onwards.

Entry is free, but, we have limited seats (50). Online registration closes on Tuesday, May 29, 2012, 2359 IST. If you are interested in attending, please add your name to https://fedoraproject.org/wiki/FAD_Pune_2012_June_02.

There will be no registration on the day of the event.

This is purely an activity based event where you are required to work on Fedora related sub-projects. There will be no talks.

Lunch will be sponsored by Red Hat. We will also have an F17 release party!

Please make sure to bring a valid photo identity card (driving license/voter’s id etc.) to enter the premises.

If you would like to suggest projects/task to work on during the FAD, please feel free to update the wiki page.

You are encouraged to bring your laptop. Please do ensure that you have all the necessary software installed for your work, or atleast:

  # yum install @development-tools fedora-packager

There will be Internet access available at the facility.

I wanted to migrate my blog to a static site generator, and chose Hakyll, since it is written in Haskell. You can install it on Fedora using:

$ sudo yum install ghc-hakyll-devel

I started looking at existing sites generated using Hakyll, and chose Ian Ross’s blog as a reference. I began customizing the same during the Hackfest organized by Changer in Pune, India on Saturday, May 5, 2012.

The 2012 posts now have permanent URLs. Posts are tagged. I have retained the CSS, current RSS feed and blog URL during this migration. You can get the sources from gitorious.org:

$ git clone git://gitorious.org/shakthimaan-blog/mainline.git

Some pictures of a used HP Pavilion dv6000 which had a fried motherboard:

Keyboard removed Keyboard Metal casing TFT Without the TFT Motherboard

data-reify provides a way to turn recursive data structures into graphs. It is now available in Fedora. Install it using:

 $ sudo yum install ghc-data-reify-devel

A list [1,2,3] can be written using Cons, Nil, and In for recursion using:

In (Cons 1 (In (Cons 2 (In (Cons 3 (In Nil))))))

An example when using data-reify for the above is given below:

{-# LANGUAGE TypeFamilies #-}
module Main where

import Control.Applicative hiding (Const)

import Data.Reify
import Control.Monad

data List a b = Nil | Cons a b
  deriving Show

instance MuRef [a] where
  type DeRef [a] = List a 

  mapDeRef f (x:xs) = Cons x <$> f xs
  mapDeRef f []     = pure Nil

main = do
        let g1 = [1, 2, 3]
        reifyGraph g1 >>= print

Compile it using:

$ ghc --make Test.hs
[1 of 1] Compiling Main             ( Test.hs, Test.o )
Linking Test ...

Run it using:

$ ./Test
let [(1,Cons 1 2),(2,Cons 2 3),(3,Cons 3 4),(4,Nil)] in 1
« OLDER POSTSNEWER POSTS »