Devember Time!

Is it too late to join now?

Itā€™s never too late but you need to put in some overtime.

1 Like

This looks sweet!!

Iā€™ve been working on my own project the last couple of days already, so while Iā€™m jumping into this late, I think that Iā€™ll sign up for this. :slightly_smiling_face:

Iā€™ll just need to move this to a public repo.

But, what Iā€™m working on right now is a budget program that I can use in my own personal life, but additionally, itā€™s so I can learn c#.
I already know Java, so picking up on c# hasnā€™t been that bad at all. However, I am still getting used to all the stuff that visual studio and c# does for you out of the box. Whew! Thereā€™s a lot!

Hey if youā€™re throwing in some JavaScript or some kind of interactivity to your comic, itā€™s perfect!

1 Like

Iā€™ve finally submitted my PhD thesis so alongside catching up on a whole bunch of reading I have been missing out on, I need to get back to actually programming stuff. I have been using D for my university projects for the past 2-3 years when I can (mostly because Iā€™m the only one using my code base) and Iā€™ve fallen in love with the language. So I think Iā€™m going to try and build up a bigger project using D - maybe some web app.

Otherwise Iā€™d quite like to try out some functional programming at some point. I know you can do bits in D but a purely functional programming language sounds worlds apart from the imperative style Iā€™m used to so it might be a good time to dive in. Either way, Iā€™m a little late but Iā€™m definitely up for getting involved!

2 Likes

Thats awesome man, canā€™t wait to see what youā€™ll cook up.

1 Like

Donā€™t really count this for the contest, not even for a Marvel Comics no-prize, but I figured Iā€™d take my old cgi-bin Fortran .csv data statistical tabulator and refactor the code
.e.g.


C SUBPROGRAM - C. A. R. HOARE'S QUICK SELECTION ALGORITHM
************************************************************************
      REAL FUNCTION QSEL(K, N, X, IDX)
      INTEGER K, N, IDX(N)
      REAL X(N)
C
C LOCAL VARIABLES
C
      INTEGER I, J, LEFT, RIGHT, TMP
      REAL PIVOT
C
C INITIALIZE INDEX ARRAY
C
      DO 100 I=1,N
        IDX(I)=I
100   CONTINUE
      LEFT=1
      RIGHT=N
200   IF (LEFT .LT. RIGHT) THEN
         PIVOT=X(IDX(K))
         I=LEFT
         J=RIGHT
         DO 500
300         IF (X(IDX(I)) .LT. PIVOT) THEN
               I=I+1
               GO TO 300
            END IF
400         IF (PIVOT .LT. X(IDX(J))) THEN
               J=J-1
               GO TO 400
            END IF
            IF (I .LE. J) THEN
               TMP=IDX(I)
               IDX(I)=IDX(J)
               IDX(J)=TMP
               I=I+1
               J=J-1
            END IF
            IF (I .GT. J) EXIT
500      CONTINUE
         IF (J .LT. K) LEFT=I
         IF (K .LT. I) RIGHT=J
         GO TO 200
      END IF
      QSEL=X(IDX(K))
      RETURN
      END
************************************************************************
C SUBPROGRAM COMPUTES MEDIAN
************************************************************************
      REAL FUNCTION MEDIAN(N, X, IDX)
      INTEGER N, IDX(N)
      REAL X(N)
C
C FUNCTIONS
C
      REAL QSEL

      IF (MOD(N, 2) .EQ. 1) THEN
         MEDIAN=QSEL(N/2+1, N, X, IDX)
      ELSE
         MEDIAN=(QSEL(N/2, N, X, IDX)+QSEL(N/2+1, N, X, IDX))/2
      END IF
      RETURN
      END

into a somewhat more Modern Fortran approach

! Modern Fortran statistical computations module

module stats_module

interface popvar
   module procedure pop_var, pop_var_avg
end interface

interface samvar
   module procedure sam_var, sam_var_avg
end interface

interface popstd
   module procedure pop_std, pop_std_avg
end interface

interface samstd
   module procedure sam_std, sam_std_avg
end interface

interface median_deviation
   module procedure median_deviation, median_deviation_avg
end interface

interface mean_deviation
   module procedure mean_deviation, mean_deviation_avg
end interface

interface skewness
   module procedure skewness, skewness_avg
end interface

contains
   ! function returns real mean of all array elements
   function mean(x, n) result(avg)

. . .

   ! functions returns index of kth element of x
   ! C. A. R. Hoare's algorithm
   ! implementation works on index array only - preserves data set array
   function quick_select(k, n, x) result(y)
      implicit none
      ! dummy arguments
      integer, intent(in) :: k, n
      real, intent(in), dimension(n) :: x
      ! local variables
      integer :: i, j, left, right, tmp
      integer, dimension(n) :: idx
      real :: pivot, y
      ! processing
      do i = 1, n
         idx(i) = i
      end do
      left = 1
      right = n
      do while (left < right)
         pivot = x(idx(k))
         i = left
         j = right
         do
            do while (x(idx(i)) < pivot)
               i = i + 1
            end do
            do while (pivot < x(idx(j)))
               j = j - 1
            end do
            if (i <= j) then
               tmp = idx(i)
               idx(i) = idx(j)
               idx(j) = tmp
               i = i + 1
               j = j - 1
            end if
            if (i > j) exit
         end do
         if (j < k) left = i
         if (k < i) right = j
      end do
      y = x(idx(k))
   end function quick_select

   ! function returns median of x
   function median(x, n) result(mdn)
      implicit none
      ! dummy arguments
      integer, intent(in) :: n
      real, intent(in), dimension(n) :: x
      ! local variables
      real :: mdn
      ! processing
      if (mod(n, 2) == 1) then
         mdn = quick_select(n/2+1, n, x)
      else
         mdn = (quick_select(n/2, n, x)+quick_select(n/2+1, n, x))/2
      end if
   end function median

. . .

   ! function computes the skewness of x
   ! overloaded version - mean average has already been computed
   ! population standard deviation has already been computed
   function skewness_avg(x, n, avg, popstd) result(skw)
      implicit none
      ! dummy arguments
      integer, intent(in) :: n
      real, intent(in) :: avg, popstd
      real, intent(in), dimension(n) :: x
      ! local variables
      integer :: i
      real :: s, skw
      ! processing
      s = 0
      do i = 1, n
         s = (((i - 1) * s) + (x(i) - avg)**3) / i
      end do
      skw = s / popstd**3
   end function skewness_avg
end module stats_module

etc. etc.
and on the presntation side of things decided to rip off some css code from here
HTML Tables with CSS Styles
In particular the part 3. HTML Table using CSS Gradients.
The end result being not much more than
Before:
before
After:
after

So that was my weekend winter fun! :slightly_smiling_face:
All this stuff is at :
fortran95-csv-stats-tabulator

3 Likes

Thatā€™s pretty neat. Reminds me of some of the stuff we have at work.

1 Like

Got my latest blog in.

Boy its been quite a ride T_T

I edited the root post to link to the devs project threads. Check them out if you havent already and give them some encouragement.

1 Like

Thatā€™s awesome, man! A lot of that went over my head, but itā€™s neat to see into the work youā€™re doing.

So far, the updates to everyoneā€™s projects is interesting.

Since were 12 days into the challenge, anyone looking to get it started now wonā€™t really be able to fully complete it, but any and all submissions are welcome.

I just want to see what awesome projects people can come up with :smiley:

1 Like

I think I want to take part in this, and I took the previous mentioned resource and read through, but is there anywhere online that has a lot of assembly stuff to teach? Its really the only code that I am interested in.

Odd to say half way through the month, sure, but I would just do it for fun for a whole year really.

Pm sent

Better late than never:

Letā€™s see how long I last

2 Likes

Iā€™ve added you to the list :smiley:

1 Like

Know Iā€™m late to the party and all, however I do have a server which I havenā€™t been using for anything but F@A, and I want to set up remote SSH with publlic key encryption along with file sharing + automation. All of this comes down to either getting into perl or python headfirst or leveling up my bash. Try to count me in.

Sure, make a post and Iā€™ll add you.

IIRC Wendel released a great guide for that on the linux channel some months ago.

Glad to see these are still going

Yeah me too. :slight_smile:

Hereā€™s a little peek of what Iā€™ve done today.

4 Likes