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:  How to represent a (running) network? (Dmitry Vyal)
   2.  Type Inference (Johannes Engels)
   3.  Type system for constructor preconditions (Bryan Vicknair)
   4. Re:  Type Inference (Johannes Engels)
   5. Re:  How to represent a (running) network? (C K Kashyap)
   6. Re:  Type system for constructor preconditions (Daniel Trstenjak)


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

Message: 1
Date: Thu, 17 Jan 2013 00:11:34 +0400
From: Dmitry Vyal <akam...@gmail.com>
Subject: Re: [Haskell-beginners] How to represent a (running) network?
To: Martin Drautzburg <martin.drautzb...@web.de>
Cc: beginners@haskell.org
Message-ID: <50f70976....@gmail.com>
Content-Type: text/plain; charset=ISO-8859-1; format=flowed

On 01/15/2013 12:51 AM, Martin Drautzburg wrote:
> What would be a good way to represent a Network anyways? I believe the classic
> approach is a list of nodes and a list vertices. In the simulation I will
> frequently have to find the process of an input or output and to find the
> input connected to an output. The node/vertices implementation seems to
> require scanning lists, which could be slow once I have thousands of
> processes.
>
> Other than that any pointers to how to construct networks (which go beyond
> mere graphs) would be much appreciated.
>
Hello Martin,
I guess the exact way depends on what precisely you want to achieve. I'm 
thinking about two options, hope others will suggest more. Either you 
try to model it in a pure setting or you go into IO.

In a former case you may try to make use of lazy streams, say function 
of type
f :: [a] -> [b] -> [c]
is basically your's processing unit which takes two inputs and produces 
one output.
For example, this is an integrator:

f1 xs ys = zipWith (+) xs ys
summer xs = let ret = f1 xs ys
                 ys = 0 : ret
             in ret

Here you depend on mutually recursive bindings in order to form the 
loops, so you can't make a dynamic structures this way, I believe.

Speaking about IO, you may either go the classic boring way by 
collecting all the outputs in some mutable data structure and updating 
them in a loop, or you may try to have some fun with GHC's green threads:

import Control.Monad
import Control.Concurrent
import Control.Concurrent.MVar

mkBinaryF f i1 i2 = do
   ret <- newEmptyMVar

   let worker = do
         v1 <- i1
         v2 <- i2
         res <- f v1 v2
         putMVar ret res
   forkIO $ forever worker
   return (takeMVar ret)

main = do
   inp2 <- newMVar 0
   out <- mkBinaryF (\x y -> return $ x + y) (getLine >>= return . read) 
(takeMVar inp2)

   forever $ do
     v <- out
     putStrLn $ "out: " ++ show v
     putMVar inp2 v

For a more theoretically backed approach I suggest you to look at CSP. 
http://www.cs.kent.ac.uk/projects/ofa/chp/

Best wishes,
Dmitry



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

Message: 2
Date: Wed, 16 Jan 2013 22:43:06 +0100
From: Johannes Engels <johannes.eng...@hft-stuttgart.de>
Subject: [Haskell-beginners] Type Inference
To: beginners@haskell.org
Message-ID: <50f71eea.6040...@hft-stuttgart.de>
Content-Type: text/plain; charset=ISO-8859-15; format=flowed

Hello,

playing around with type classes, I came up with the idea to implement 
Matlab-like array slices by overloading the (!) - Operator. My first try 
goes

 > {-# LANGUAGE MultiParamTypeClasses ,
 >             FunctionalDependencies ,
 >             FlexibleContexts ,
 >             FlexibleInstances  #-}

 > import Data.Array.Unboxed hiding ((!))
 > import qualified Data.Array.Unboxed as AU


 > class Sliceable arrtype indtype resulttype | arrtype indtype -> 
resulttype
 >         where (!) :: arrtype -> indtype -> resulttype

 > instance (Ix i, IArray UArray e) => Sliceable (UArray i e) i e
 >   where (!) = (AU.!)

 > instance (Ix i, IArray UArray e) => Sliceable (UArray i e) [i] 
(UArray Int e)
 >   where (!) arr ilist = listArray (0,end_ind) [(AU.!) arr i | i <- ilist]
 >               where end_ind = length ilist - 1



In principle this seems to work, for instance

ghci>  let arr = listArray (0,99) [0..99] :: UArray Int Double
ghci>  arr ! (17::Int)
17.0
ghci>  arr ! [13..15 :: Int]
array (0,2) [(0,13.0),(1,14.0),(2,15.0)]

However, the ugly type annotations (::Int) are necessary, otherwise I 
get an error message:

 > arr ! 17

No instance for (Sliceable (UArray Int Double) indtype0 resulttype0)
    arising from a use of `!'
Possible fix:
    add an instance declaration for
    Sliceable (UArray Int Double) indtype resulttype0
    in the expression: arr ! 17


whereas the type annotation is not necessary for the original 
Array.Unboxed - (!) :
 > (AU.!) arr 17
17.0

Could somebody please explain why the type annotation is necessary in my 
case? Is there a trick to circumvent this? Any hint would be welcome!

Best regards
Johannes












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

Message: 3
Date: Wed, 16 Jan 2013 15:10:18 -0800
From: Bryan Vicknair <bryanv...@gmail.com>
Subject: [Haskell-beginners] Type system for constructor preconditions
To: beginners@haskell.org
Message-ID:
        <camejusy_pyvzwk-zugjjzzsnmndud+anydry85fmta59j81...@mail.gmail.com>
Content-Type: text/plain; charset=ISO-8859-1

I'm interested in forcing data passed to a constructor to meet certain
preconditions.  I've seen the wiki entry on smart constructors, and would have
stopped thinking about the problem if hiding the data constructors didn't also
make it impossible to do pattern matching.

Ideally, the type system could do these checks, but we don't have dependent
types so I kept looking.  The pattern below uses the type system to force a
client of the Circle data type to pass in valid (positive) radius.  This isn't
quite what is on the smart constructors wiki page.  Does pattern have a name?
Where can I read more about it?  What are the negatives?

The positives are that when a client goes to create a Circle in their code,
they'll notice that they need to pass a ValidRadius, not just any number, so
then they'll *have* to find a function that gives them a ValidRadius, and thus
will be forced to be semi-informed about what sorts of preconditions exist on
the Circle constructor;  They'll have to deal with the case that validRadius
gives them Nothing.

If we had simply put a comment by the Circle constructor to use a
validateRadius function to make sure their number is valid, they could have
ignored it.


-- In Circle.hs
module Circle (
    Circle (Circle),
    Radius,
    validRadius,
    ValidRadius
    ) where

type Radius = Int
data ValidRadius = ValidRadius Radius deriving (Eq, Show)
data Circle = Circle ValidRadius deriving (Eq, Show)

-- A radius must be positive.
validRadius :: Radius -> Maybe ValidRadius
validRadius x
  | x > 0     = Just $ ValidRadius x
  | otherwise = Nothing



-- In Client.hs
import Circle

r = 3 :: Radius
vr :: ValidRadius
vr = case validRadius r of
          Nothing -> error "Tell UI about bad input"
          Just x  -> x



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

Message: 4
Date: Thu, 17 Jan 2013 08:41:31 +0100
From: Johannes Engels <johannes.eng...@hft-stuttgart.de>
Subject: Re: [Haskell-beginners] Type Inference
To: beginners@haskell.org
Message-ID: <50f7ab2b.2040...@hft-stuttgart.de>
Content-Type: text/plain; charset=ISO-8859-1; format=flowed

Am 16.01.2013 23:48, schrieb Lemol Morais Lutonda:
>
> You realy need a generic indtype? what if to define it just as a Int?
>
>
> 48 Aniversario del Instituto Superior Politecnico Jose Antonio 
> Echeverria, Cujae
> Una obra de la Revolucion Cubana | 2 de diciembre de 1964 | 
> http://cujae.edu.cu
>
>
> Consulte la enciclopedia colaborativa cubana. http://www.ecured.cu
>

You are right that I don't need a generic indtype in the instance 
declarations, the following would be sufficient for me:

 > instance Sliceable (UArray Int Double) Int Double
 >    where (!) = (AU.!)

 > instance Sliceable (UArray Int Double) [Int] (UArray Int Double)
 >    where (!) arr ilist = listArray (0,end_ind) [(AU.!) arr i | i <- 
ilist]
 >               where end_ind = length ilist - 1

But also for this case a type annotation is necessary as in my original 
post. And within the class definition I think I need a generic indtype, 
because I want to be able to use arguments of type Int as well as [Int] 
as the second argument of (!).






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

Message: 5
Date: Thu, 17 Jan 2013 14:36:41 +0530
From: C K Kashyap <ckkash...@gmail.com>
Subject: Re: [Haskell-beginners] How to represent a (running) network?
To: Dmitry Vyal <akam...@gmail.com>
Cc: beginners <beginners@haskell.org>
Message-ID:
        <CAGdT1gqj1HmPcScTysZ-gKAV4_ntaP14UhLP1Y+=8oq8jhk...@mail.gmail.com>
Content-Type: text/plain; charset="iso-8859-1"

Hi Martin,
Does http://computing.unn.ac.uk/staff/cgdh1/projects/funcsimul.txt sound
like what you need?
Regards,
Kashyap


On Thu, Jan 17, 2013 at 1:41 AM, Dmitry Vyal <akam...@gmail.com> wrote:

> On 01/15/2013 12:51 AM, Martin Drautzburg wrote:
>
>> What would be a good way to represent a Network anyways? I believe the
>> classic
>> approach is a list of nodes and a list vertices. In the simulation I will
>> frequently have to find the process of an input or output and to find the
>> input connected to an output. The node/vertices implementation seems to
>> require scanning lists, which could be slow once I have thousands of
>> processes.
>>
>> Other than that any pointers to how to construct networks (which go beyond
>> mere graphs) would be much appreciated.
>>
>>  Hello Martin,
> I guess the exact way depends on what precisely you want to achieve. I'm
> thinking about two options, hope others will suggest more. Either you try
> to model it in a pure setting or you go into IO.
>
> In a former case you may try to make use of lazy streams, say function of
> type
> f :: [a] -> [b] -> [c]
> is basically your's processing unit which takes two inputs and produces
> one output.
> For example, this is an integrator:
>
> f1 xs ys = zipWith (+) xs ys
> summer xs = let ret = f1 xs ys
>                 ys = 0 : ret
>             in ret
>
> Here you depend on mutually recursive bindings in order to form the loops,
> so you can't make a dynamic structures this way, I believe.
>
> Speaking about IO, you may either go the classic boring way by collecting
> all the outputs in some mutable data structure and updating them in a loop,
> or you may try to have some fun with GHC's green threads:
>
> import Control.Monad
> import Control.Concurrent
> import Control.Concurrent.MVar
>
> mkBinaryF f i1 i2 = do
>   ret <- newEmptyMVar
>
>   let worker = do
>         v1 <- i1
>         v2 <- i2
>         res <- f v1 v2
>         putMVar ret res
>   forkIO $ forever worker
>   return (takeMVar ret)
>
> main = do
>   inp2 <- newMVar 0
>   out <- mkBinaryF (\x y -> return $ x + y) (getLine >>= return . read)
> (takeMVar inp2)
>
>   forever $ do
>     v <- out
>     putStrLn $ "out: " ++ show v
>     putMVar inp2 v
>
> For a more theoretically backed approach I suggest you to look at CSP.
> http://www.cs.kent.ac.uk/**projects/ofa/chp/<http://www.cs.kent.ac.uk/projects/ofa/chp/>
>
> Best wishes,
> Dmitry
>
>
> ______________________________**_________________
> Beginners mailing list
> Beginners@haskell.org
> http://www.haskell.org/**mailman/listinfo/beginners<http://www.haskell.org/mailman/listinfo/beginners>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20130117/b7c97bc7/attachment-0001.htm>

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

Message: 6
Date: Thu, 17 Jan 2013 10:41:26 +0100
From: Daniel Trstenjak <daniel.trsten...@gmail.com>
Subject: Re: [Haskell-beginners] Type system for constructor
        preconditions
To: beginners@haskell.org
Message-ID: <20130117094126.GA3703@machine>
Content-Type: text/plain; charset=us-ascii


Hi Bryan,

On Wed, Jan 16, 2013 at 03:10:18PM -0800, Bryan Vicknair wrote:
> Ideally, the type system could do these checks, but we don't have dependent
> types so I kept looking.  The pattern below uses the type system to force a
> client of the Circle data type to pass in valid (positive) radius.  This isn't
> quite what is on the smart constructors wiki page.  Does pattern have a name?
> Where can I read more about it?  What are the negatives?

It's just a smart constructor. Instead of using one for Circle, you are
now using one for ValidRadius.

You still have the same pattern matching issue, because how would you
access the radius inside of ValidRadius?

But instead of using pattern matching to access the fields of Circle
you could offer accessor functions.


module Circle (Circle, Radius, circle, radius) where

type Radius = Int
data Circle = Circle Radius deriving (Eq, Show)

circle :: Radius -> Maybe Circle
circle r | r > 0     = Just $ Circle r
         | otherwise = Nothing

radius :: Circle -> Radius
radius (Circle r) = r
   

Greetings,
Daniel



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

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


End of Beginners Digest, Vol 55, Issue 17
*****************************************

Reply via email to