Send Beginners mailing list submissions to
        beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
        http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
        beginners-requ...@haskell.org

You can reach the person managing the list at
        beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than "Re: Contents of Beginners digest..."


Today's Topics:

   1. Re:  using record in aeson (David McBride)
   2. Re:  How would you improve this program? (Lorenzo Bolla)
   3.  Data structure for Propositional Logic formulas
      (Alexander Raasch)
   4.  first open source haskell project and a mystery  to boot (Alia)
   5. Re:  Data structure for Propositional Logic       formulas
      (Daniel Schoepe)
   6. Re:  Data structure for Propositional Logic       formulas
      (Benedict Eastaugh)


----------------------------------------------------------------------

Message: 1
Date: Wed, 12 Oct 2011 11:21:03 -0400
From: David McBride <toa...@gmail.com>
Subject: Re: [Haskell-beginners] using record in aeson
To: Rick Murphy <r...@rickmurphy.org>
Cc: beginners@haskell.org
Message-ID:
        <can+tr429fqfblzybg4hujz8pfadqjnbpff1ycd6drbppcz7...@mail.gmail.com>
Content-Type: text/plain; charset=ISO-8859-1

The problem is that in parseObject, from the moment you type 'return',
you are then in pure code.  But you are trying to do applicative
functions as if you are still in the Parser monad.  Here is a way to
rewrite this.

First rewrite
data MyRecord = MyRecord {s :: T.Text, u :: T.Text} deriving (Show)
because we are using Text not String, then

parseObject o' = mapM toMyPair (M.assocs o')
  where
    toMyPair :: (T.Text, Value) -> J.Parser MyPair
    toMyPair (t, Object o'') = do
      rec <- MyRecord <$> (o'' .: "type") <*> (o'' .: "value") ::
J.Parser MyRecord
      return $ R (t, rec)
    toMyPair _              = error "unexpected"

That is, stay in the parser monad and pull out the things you need
using do notation, then return the whole thing back into the parser
monad.  You could have also gone:

    toMyPair (t, Object o'') = do
      typ <- o'' .: "type"
      val <- o'' .: "value"
      return $ R (t, MyRecord typ val)


On Tue, Oct 11, 2011 at 9:17 PM, Rick Murphy <r...@rickmurphy.org> wrote:
> Hi All:
>
> I've been elaborating on aeson examples and wondered whether someone
> could clarify the syntax for using a record in a pair. My goal is to
> substitute a record for the list of pairs created through the data
> constructor O [(T.Text, Value)] in MyPair below. Reason being to embed
> the semantics of the json file into the record. To reproduce, just
> uncomment the lines in the source below.
>
> The json file structure is as follows:
> {"outer":{"type":"literal","value":"rick"}}
>
> Note my naive attempt in the commented lines returns the following
> message from ghci. 'f0 b0' doesn't give me much to go on.
>
> -- E1.hs:35:41:
> -- ? ? Couldn't match expected type `MyRecord' with actual type `f0 b0'
> -- ? ? In the expression: MyRecord <$> o'' .: "type" <*> o'' .: "value"
> -- ? ? In the first argument of `R', namely
> -- ? ? ? `(t, MyRecord <$> o'' .: "type" <*> o'' .: "value")'
> -- ? ? In the expression: R (t, MyRecord <$> o'' .: "type" <*> o'' .:
> "value")
> -- Failed, modules loaded: none.
>
> {-# LANGUAGE OverloadedStrings #-}
>
> module Main where
>
> import Control.Applicative
> import Control.Monad (mzero)
>
> import qualified Data.ByteString as B
> import qualified Data.Map as M
> import qualified Data.Text as T
>
> import Data.Aeson
> import qualified Data.Aeson.Types as J
> import Data.Attoparsec
>
> -- data MyRecord = MyRecord {s :: String, u :: String} deriving (Show)
>
> data MyPair = O (T.Text, [(T.Text, Value)])
> ? ? ? ? ? -- | R (T.Text, MyRecord)
> ? ? ? ? ? ? ?deriving (Show)
>
> data ExifObject = ExifObject [MyPair]
> ? ? ? ? ? ? ? ?deriving Show
>
> data Exif ? ? ? = Exif [ExifObject]
> ? ? ? ? ? ? ? ?deriving Show
>
> instance FromJSON ExifObject
> ?where
> ? ?parseJSON (Object o) = ExifObject <$> parseObject o
> ? ? ?where
> ? ? ? ?parseObject o' = return $ map toMyPair (M.assocs o')
>
> ? ? ? ?toMyPair (t, Object o'')= O (t, M.assocs o'')
> -- ? ? ?toMyPair (t, Object o'')= R (t, MyRecord <$> o'' .: "type" <*>
> o'' .: "value")
> ? ? ? ?toMyPair _ ? ? ? ? ? ? ?= error "unexpected"
>
> ? ?parseJSON _ ? ? ? ? ?= mzero
>
> parseAll :: B.ByteString -> [ExifObject]
> parseAll s = case (parse (fromJSON <$> json) s) of
> ?Done _ (Error err) ?-> error err
> ?Done ss (Success e) -> e:(parseAll ss)
> ?_ ? ? ? ? ? ? ? ? ? -> []
>
> main :: IO ()
> main = do s <- B.readFile "e1.json"
> ? ? ? ? ?let p = Exif $ parseAll s
> ? ? ? ? ?print p
>
> --
> Rick
>
>
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://www.haskell.org/mailman/listinfo/beginners
>



------------------------------

Message: 2
Date: Wed, 12 Oct 2011 16:25:31 +0100
From: Lorenzo Bolla <lbo...@gmail.com>
Subject: Re: [Haskell-beginners] How would you improve this program?
To: beginners@haskell.org
Message-ID:
        <cadjgtrwdyvdhhojq0tyyfvj4fqlzsj7yto96k+dqr25lgea...@mail.gmail.com>
Content-Type: text/plain; charset="utf-8"

On Tue, Oct 11, 2011 at 4:28 PM, Brent Yorgey <byor...@seas.upenn.edu>wrote:

> On Tue, Oct 11, 2011 at 02:04:23PM +0300, Ovidiu Deac wrote:
>
> >     join "\n" result -- from Data.List.Utils
>
> By the way, 'join "\n" result' is better written 'unlines result' (and
> 'join' is better written 'intercalate'). (Otherwise I completely agree
> with your email.)
>
>
Fixed.
https://github.com/lbolla/stanford-cs240h/blob/master/lab1/lab1.hs

Thanks for the suggestions.
L.
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20111012/0a724bf6/attachment-0001.htm>

------------------------------

Message: 3
Date: Wed, 12 Oct 2011 17:38:51 +0200
From: Alexander Raasch <i...@alexraasch.de>
Subject: [Haskell-beginners] Data structure for Propositional Logic
        formulas
To: beginners@haskell.org
Message-ID: <4e95b48b.3040...@alexraasch.de>
Content-Type: text/plain; charset=ISO-8859-1; format=flowed

Hi,

I wrote this program to work with formulas in propositional logic:

data Formula =
               | Variable Char
               | Not Formula | And Formula Formula | Or Formula Formula
               | Imply Formula Formula | Equivalent Formula Formula
               deriving (Eq)

instance Show Formula where
    show (Variable v) = [v]
    show (Not f)      = "~" ++ show f
    show (And f g)    = "(" ++ show f ++ " & " ++ show g ++ ")"
    show (Or f g)     = "(" ++ show f ++ " v " ++ show g ++ ")"
    show (Imply f g ) = "(" ++ show f ++ " -> " ++ show g ++ ")"
    show (Equivalent f g ) = "(" ++ show f ++ " <-> " ++ show g ++ ")"

To make a formula you can do something like:

ghci> let f = Or (Variable 'C') (And (Variable 'A') (Not (Variable 'C')))
ghci> f
(C v (A & ~C))

So, my questions are:

1. Do you think this is an elegant solution or would you define custom 
operators (or, and, ->, <->) instead? Or something completely different?
2. If I pack this code into a module how would add a new logic 
connective like xor or nand to Formula? Meaning, can I add another type 
constructor to it?
3. Is there a way to "nest" data definitions, e.g. I would like to 
replace the 'Variable Char' type constructor by 'Literal Char', whereas 
a Literal is either a Variable or a negated Variable. Literals can be 
negated, too.

Thanks a lot.
Alex



------------------------------

Message: 4
Date: Wed, 12 Oct 2011 11:59:30 -0700 (PDT)
From: Alia <alia_kho...@yahoo.com>
Subject: [Haskell-beginners] first open source haskell project and a
        mystery to boot
To: "beginners@haskell.org" <beginners@haskell.org>
Message-ID:
        <1318445970.70480.yahoomail...@web65710.mail.ac4.yahoo.com>
Content-Type: text/plain; charset=iso-8859-1

Hi folks,

Given that I received such excellent help from this newsgroup recently, I 
wanted to share my first 

open-source haskell project available here: 
https://github.com/aliakhouri/newsagent

It's a simple command line feed (atom, rss) retriever and analyzer in the early 
stages of development, 

using the excellent feed / tagsoup libs to download and analyze feeds from the 
net.

The real intention is to use it as a platform to learn about information 
retrieval and machine learning 

techniques in haskell.


To this end, I was searching for classification algorithms and I was on the 
lookout for a nice
clear implementation in haskell of canonical decision tree based classification 
algorithms.


My first discovery was an old DecisionTree package on hackage but it's poorly 
documented 

and has no examples of usage. So I kept searching...


Then I found an hpaste page (http://hpaste.org/steps/11355) which looked at lot 
more 

promising, but it also has no example or documentation. In fact, it's an island 
of code without 

any references (I don't know who the author is) and nobody has ever referred to 
it by url or by
blog post). It's a mystery to me.


In any case, I've tried to create a working example but I'm stuck because you 
can't mix 

strings and numbers in a list, and I can't decide whether that's when the 
author gave up, 

or whether I've missed the point. Like I said it's a mystery.

I would appreciate if anyone could shed some light on this whimsical problem.


In case you are wondering why this is relevant to the beginner's forum. Well...

firstly, I am a beginner, and, er... the code is short enough to serve 
pedagogical purposes? (-;



AK

<ID3.hs>
-- | This module is a generic implementation
--?? of the ID3 decision tree algorithm.
--
-- A choice node on a ``continuous'' attribute is
-- handled by splitting the population in two via the mean attribute value.

module ID3 where

import Data.Ord
import Data.List
import qualified Data.Map as Map

data DecisionTree item outcome = Choice (item -> DecisionTree item outcome)
?????????????????????????????? | Leaf outcome

data Attribute item = Discrete (item -> Integer)
??????????????????? | Continuous (item -> Double)


runDecisionTree :: DecisionTree item outcome -> item -> outcome
runDecisionTree (Leaf outcome) _ = outcome
runDecisionTree (Choice f) item = runDecisionTree (f item) item

id3 :: (Ord outcome) => [Attribute item] -> [(item, outcome)] -> DecisionTree 
item outcome
-- When there are no unused attributes left, select the most common outcome.
id3 [] xs = Leaf $ fst $ head $ sortBy (comparing (negate.snd)) $ histogram 
(map snd xs)
-- When all the items have the same outcome, pick that outcome
id3 attrs xs | allEqual (map snd xs) = Leaf $ snd $ head xs
-- Otherwise pick the attribute with minimum entropy
???????????? | otherwise =
??? let (bestAttr:moreAttrs) = sortBy (comparing (informationGain xs)) attrs in
??? case bestAttr of
???????? Discrete attr ->
???????????? let attrTreeMap = Map.fromList attrTrees
???????????????? allAttrValues = nub $ map (attr . fst) xs
???????????????? subtree v = id3 moreAttrs (filter (\(x,_) -> v /= attr x) xs)
???????????????? attrTrees = [(v, subtree v) | v <- allAttrValues]
???????????? in Choice $ \item -> case Map.lookup (attr item) attrTreeMap of
?????????????????????????????????????? Just subtree -> subtree
?????????????????????????????????????? Nothing -> error "id3: encountered a 
discrete attribute value that wasn't in the training set"
???????? Continuous attr ->
???????????? let meanv = mean (map (attr.fst) xs)
???????????????? ltTree = id3 moreAttrs (filter (\(x,_) -> attr x <? meanv) xs)
???????????????? gtTree = id3 moreAttrs (filter (\(x,_) -> attr x >= meanv) xs)
???????????? in Choice $ \item -> if attr item < meanv
???????????????????????????????????? then ltTree
???????????????????????????????????? else gtTree

informationGain :: Ord outcome => [(item, outcome)] -> Attribute item -> Double
informationGain xs (Discrete attr) =
??? currentEntropy - sum (map term allAttributeValues)
??? where
??? currentEntropy = entropy (map snd xs)
??? term a = probabilityOf (==a) * entropy (outcomesFor (==a))
??? probabilityOf f = fromIntegral (length (outcomesFor f)) / fromIntegral 
(length xs)
??? outcomesFor f = map snd $ filter (f . attr . fst) xs
??? allAttributeValues = nub $ map (attr . fst) xs
informationGain xs (Continuous attr) =
??? currentEntropy - term (< meanv) - term (>= meanv)
??? where
??? currentEntropy = entropy (map snd xs)
??? term f = probabilityOf f * entropy (outcomesFor f)
??? probabilityOf f = fromIntegral (length (outcomesFor f)) / fromIntegral 
(length xs)
??? outcomesFor f = map snd $ filter (f . attr . fst) xs
??? meanv = mean (map (attr.fst) xs)

entropy :: Ord a => [a] -> Double
entropy xs = sum $ map (\(_,n) -> term (fromIntegral n)) $ histogram xs
??? where term 0 = 0
????????? term n = - (n / num) * log (n / num) / log 2
????????? num = fromIntegral (length xs)

histogram :: Ord a => [a] -> [(a, Int)]
histogram = buildHistogram Map.empty
??? where buildHistogram map [] = Map.assocs map
????????? buildHistogram map (x:xs) = buildHistogram (Map.insertWith (+) x 1 
map) xs

-- Simple "utility" functions
allEqual :: Eq a => [a] -> Bool
allEqual = and . mapAdjacent (==)

mapAdjacent :: (a -> a -> b) -> [a] -> [b]
mapAdjacent f xs = zipWith f xs (tail xs)

mean :: (Real a, Fractional n) => [a] -> n
mean xs = realToFrac (sum xs) / realToFrac (length xs)


--------------------------------------------------------------------
-- Testing Area
--------------------------------------------------------------------
outlook s
??? | s == "sunny"??? = 1
??? | s == "overcast" = 2
??? | s == "rain"???? = 3

temp :: (Real a, Fractional n) => a -> n
temp i = (realToFrac i) / (realToFrac 100)

humidity :: (Real a, Fractional n) => a -> n
humidity i = (realToFrac i) / (realToFrac 100)


windy x
??? | x == False = 0
??? | x == True? = 1

-- attributes
a1 = Discrete outlook
a2 = Continuous temp
a3 = Continuous humidity
a4 = Discrete windy

outlookData? = 
["sunny","sunny","overcast","rain","rain","rain","overcast","sunny","sunny","rain","sunny","overcast","overcast","rain"]
tempData???? = [85, 80, 83, 70, 68, 65, 64, 72, 69, 75, 75, 72, 81, 71]
humidityData = [85, 90, 78, 96, 80, 70, 65, 95, 70, 80, 70, 90, 75, 80]
windyData??? = [False, True, False, False, False, True, True, False, False, 
False, True, True, False, True]
outcomes???? = [0,0,1,1,1,0,1,0,1,1,1,1,1,0]

d1 = zip outlookData outcomes
d2 = zip tempData outcomes
d3 = zip humidityData outcomes
d4 = zip windyData outcomes

t1 = id3 [a1] d1
t2 = id3 [a2] d2
t3 = id3 [a3] d3
t4 = id3 [a4] d4

--t5 = id3 [a1,a2,a3,a4] [d1,d2,d3,d4] 
-- doesn't work because you can't mix strings and numbers in a list
-- 

----------------

</ID3.hs>



------------------------------

Message: 5
Date: Wed, 12 Oct 2011 22:58:47 +0200
From: Daniel Schoepe <dan...@schoepe.org>
Subject: Re: [Haskell-beginners] Data structure for Propositional
        Logic   formulas
To: Alexander Raasch <i...@alexraasch.de>, beginners@haskell.org
Message-ID: <877h4ac4fs.fsf@gilead.invalid>
Content-Type: text/plain; charset="us-ascii"

On Wed, 12 Oct 2011 17:38:51 +0200, Alexander Raasch <i...@alexraasch.de> wrote:
> Hi,
> 
> I wrote this program to work with formulas in propositional logic:
> 
> data Formula =
>                | Variable Char
>                | Not Formula | And Formula Formula | Or Formula Formula
>                | Imply Formula Formula | Equivalent Formula Formula
>                deriving (Eq)

It would be better to have Formula only include a few basic primitives
(And, Or and Not is a popular choice), and define the rest in terms of
those. More on that in the answer to your second question.

> instance Show Formula where
>     show (Variable v) = [v]
>     show (Not f)      = "~" ++ show f
>     show (And f g)    = "(" ++ show f ++ " & " ++ show g ++ ")"
>     show (Or f g)     = "(" ++ show f ++ " v " ++ show g ++ ")"
>     show (Imply f g ) = "(" ++ show f ++ " -> " ++ show g ++ ")"
>     show (Equivalent f g ) = "(" ++ show f ++ " <-> " ++ show g ++ ")"
> 
> To make a formula you can do something like:
> 
> ghci> let f = Or (Variable 'C') (And (Variable 'A') (Not (Variable 'C')))
> ghci> f
> (C v (A & ~C))
> 
> So, my questions are:
> 
> 1. Do you think this is an elegant solution or would you define custom 
> operators (or, and, ->, <->) instead? Or something completely
> different?

You can still define such operators afterwards, and I think it would
make formulas easier to read and write, for example:

(<&&>) :: Formula -> Formula
a <&&> b = And a b

> 2. If I pack this code into a module how would add a new logic 
> connective like xor or nand to Formula? Meaning, can I add another type 
> constructor to it?

If you chose a set of "primitives" capable of expressing every other
formula, you can define xor, nand, etc. later as normal functions:

nand :: Formula -> Formula -> Formula
nand a b = Not (And a b)

> 3. Is there a way to "nest" data definitions, e.g. I would like to 
> replace the 'Variable Char' type constructor by 'Literal Char', whereas 
> a Literal is either a Variable or a negated Variable. Literals can be 
> negated, too.

The parameters to constructors are not limited to built-in types and the
type you are defining. So for your example, something like this would
work:

data Literal = Variable Char | NegVar Char

data Formula = Literal | And .......

That would of course introduce some redundancy, since `Not (Variable c)'
and `NegVar c' would represent the same formula.

Cheers,
Daniel
-------------- next part --------------
A non-text attachment was scrubbed...
Name: not available
Type: application/pgp-signature
Size: 835 bytes
Desc: not available
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20111012/0ce2251c/attachment-0001.pgp>

------------------------------

Message: 6
Date: Wed, 12 Oct 2011 22:24:04 +0100
From: Benedict Eastaugh <ionf...@gmail.com>
Subject: Re: [Haskell-beginners] Data structure for Propositional
        Logic   formulas
To: Alexander Raasch <i...@alexraasch.de>
Cc: beginners@haskell.org
Message-ID:
        <caoco6ulcpw7ji74qrcjpxrujeoeggcxhvwxsz8xu_2eapju...@mail.gmail.com>
Content-Type: text/plain; charset=ISO-8859-1

Hi Alex,

since Daniel has done a nice job of actually answering your questions,
I shall just note that I have a module similar to this available on
Hackage as part of my hatt package, which generates truth tables for
formulae in classical propositional logic.

http://hackage.haskell.org/package/hatt
http://hackage.haskell.org/packages/archive/hatt/1.3.0/doc/html/Data-Logic-Propositional.html

Benedict



------------------------------

_______________________________________________
Beginners mailing list
Beginners@haskell.org
http://www.haskell.org/mailman/listinfo/beginners


End of Beginners Digest, Vol 40, Issue 16
*****************************************

Reply via email to